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

module Wire.API.Routes.Internal.Galley where

import Control.Lens ((.~))
import Data.Domain
import Data.Id as Id
import Data.OpenApi (OpenApi, info, title)
import Data.Range
import GHC.TypeLits (AppendSymbol)
import Imports hiding (head)
import Servant
import Servant.OpenApi
import Wire.API.Bot
import Wire.API.Bot.Service
import Wire.API.Conversation
import Wire.API.Conversation.Role
import Wire.API.CustomBackend
import Wire.API.Error
import Wire.API.Error.Galley
import Wire.API.Event.Conversation
import Wire.API.FederationStatus
import Wire.API.Provider.Service (ServiceRef)
import Wire.API.Routes.Features
import Wire.API.Routes.Internal.Brig.EJPD
import Wire.API.Routes.Internal.Galley.ConversationsIntra
import Wire.API.Routes.Internal.Galley.TeamFeatureNoConfigMulti
import Wire.API.Routes.Internal.Galley.TeamsIntra
import Wire.API.Routes.MultiVerb
import Wire.API.Routes.Named
import Wire.API.Routes.Public
import Wire.API.Routes.Public.Galley.Conversation
import Wire.API.Routes.Public.Galley.Feature
import Wire.API.Routes.Public.Util
import Wire.API.Routes.QualifiedCapture
import Wire.API.Routes.Version
import Wire.API.Team
import Wire.API.Team.Feature
import Wire.API.Team.Member
import Wire.API.Team.SearchVisibility
import Wire.API.User.Client

type family IFeatureAPI1 cfg where
  -- special case for classified domains, since it cannot be set
  IFeatureAPI1 ClassifiedDomainsConfig = IFeatureStatusGet ClassifiedDomainsConfig
  IFeatureAPI1 cfg = IFeatureAPI1Full cfg

type IFeatureAPI1Full cfg =
  IFeatureStatusGet cfg
    :<|> IFeatureStatusPut cfg
    :<|> IFeatureStatusPatch cfg

type family IAllFeaturesAPI cfgs where
  IAllFeaturesAPI '[cfg] = IFeatureAPI1 cfg
  IAllFeaturesAPI (cfg : cfgs) = IFeatureAPI1 cfg :<|> IAllFeaturesAPI cfgs

type IFeatureAPI =
  IAllFeaturesAPI Features
    -- legacy lock status put endpoints
    :<|> IFeatureStatusLockStatusPut FileSharingConfig
    :<|> IFeatureStatusLockStatusPut ConferenceCallingConfig
    :<|> IFeatureStatusLockStatusPut SelfDeletingMessagesConfig
    :<|> IFeatureStatusLockStatusPut GuestLinksConfig
    :<|> IFeatureStatusLockStatusPut SndFactorPasswordChallengeConfig
    :<|> IFeatureStatusLockStatusPut MLSConfig
    :<|> IFeatureStatusLockStatusPut OutlookCalIntegrationConfig
    :<|> IFeatureStatusLockStatusPut MlsE2EIdConfig
    :<|> IFeatureStatusLockStatusPut MlsMigrationConfig
    :<|> IFeatureStatusLockStatusPut EnforceFileDownloadLocationConfig
    -- special endpoints
    :<|> IFeatureNoConfigMultiGet SearchVisibilityInboundConfig
    -- all feature configs
    :<|> Named
           "feature-configs-internal"
           ( Summary "Get all feature configs (for user/team; if n/a fall back to site config)."
               :> "feature-configs"
               :> CanThrow OperationDenied
               :> CanThrow 'NotATeamMember
               :> CanThrow 'TeamNotFound
               :> QueryParam'
                    [ Optional,
                      Strict,
                      Description "Optional user id"
                    ]
                    "user_id"
                    UserId
               :> Get '[JSON] AllTeamFeatures
           )

type InternalAPI = "i" :> InternalAPIBase

type InternalAPIBase =
  Named
    "status"
    ( "status" :> MultiVerb 'GET '[JSON] '[RespondEmpty 200 "OK"] ()
    )
    -- This endpoint can lead to the following events being sent:
    -- - MemberLeave event to members for all conversations the user was in
    :<|> Named
           "delete-user"
           ( Summary
               "Remove a user from their teams and conversations and erase their clients"
               :> ZLocalUser
               :> ZOptConn
               :> "user"
               :> MultiVerb 'DELETE '[JSON] '[RespondEmpty 200 "Remove a user from Galley"] ()
           )
    -- This endpoint can lead to the following events being sent:
    -- - ConvCreate event to self, if conversation did not exist before
    -- - ConvConnect event to self, if other didn't join the connect conversation before
    :<|> Named
           "connect"
           ( Summary "Create a connect conversation (deprecated)"
               :> CanThrow 'ConvNotFound
               :> CanThrow 'InvalidOperation
               :> CanThrow 'NotConnected
               :> CanThrow UnreachableBackends
               :> ZLocalUser
               :> ZOptConn
               :> "conversations"
               :> "connect"
               :> ReqBody '[JSON] Connect
               :> ConversationVerb 'V6 Conversation
           )
    -- This endpoint is meant for testing membership of a conversation
    :<|> Named
           "get-conversation-clients"
           ( Summary "Get mls conversation client list"
               :> CanThrow 'ConvNotFound
               :> "group"
               :> Capture "gid" GroupId
               :> MultiVerb1
                    'GET
                    '[JSON]
                    (Respond 200 "Clients" ClientList)
           )
    :<|> Named
           "guard-legalhold-policy-conflicts"
           ( "guard-legalhold-policy-conflicts"
               :> CanThrow 'MissingLegalholdConsent
               :> CanThrow 'MissingLegalholdConsentOldClients
               :> ReqBody '[JSON] GuardLegalholdPolicyConflicts
               :> MultiVerb1 'PUT '[JSON] (RespondEmpty 200 "Guard Legalhold Policy")
           )
    :<|> ILegalholdWhitelistedTeamsAPI
    :<|> ITeamsAPI
    :<|> IMiscAPI
    :<|> Named
           "upsert-one2one"
           ( Summary "Create or Update a connect or one2one conversation."
               :> "conversations"
               :> "one2one"
               :> "upsert"
               :> ReqBody '[JSON] UpsertOne2OneConversationRequest
               :> MultiVerb1 'POST '[JSON] (RespondEmpty 200 "Upsert One2One Policy")
           )
    :<|> IFeatureAPI
    :<|> IFederationAPI
    :<|> IConversationAPI
    :<|> IEJPDAPI

type ILegalholdWhitelistedTeamsAPI =
  "legalhold"
    :> "whitelisted-teams"
    :> Capture "tid" TeamId
    :> ILegalholdWhitelistedTeamsAPIBase

type ILegalholdWhitelistedTeamsAPIBase =
  Named
    "set-team-legalhold-whitelisted"
    (MultiVerb1 'PUT '[JSON] (RespondEmpty 200 "Team Legalhold Whitelisted"))
    :<|> Named
           "unset-team-legalhold-whitelisted"
           (MultiVerb1 'DELETE '[JSON] (RespondEmpty 204 "Team Legalhold un-Whitelisted"))
    :<|> Named
           "get-team-legalhold-whitelisted"
           ( MultiVerb
               'GET
               '[JSON]
               '[ RespondEmpty 404 "Team not Legalhold Whitelisted",
                  RespondEmpty 200 "Team Legalhold Whitelisted"
                ]
               Bool
           )

type ITeamsAPI = "teams" :> Capture "tid" TeamId :> ITeamsAPIBase

type ITeamsAPIBase =
  Named "get-team-internal" (CanThrow 'TeamNotFound :> Get '[JSON] TeamData)
    :<|> Named
           "create-binding-team"
           ( ZUser
               :> ReqBody '[JSON] NewTeam
               :> MultiVerb1
                    'PUT
                    '[JSON]
                    ( WithHeaders
                        '[Header "Location" TeamId]
                        TeamId
                        (RespondEmpty 201 "OK")
                    )
           )
    :<|> Named
           "delete-binding-team"
           ( CanThrow 'NoBindingTeam
               :> CanThrow 'NotAOneMemberTeam
               :> CanThrow 'DeleteQueueFull
               :> CanThrow 'TeamNotFound
               :> QueryFlag "force"
               :> MultiVerb1 'DELETE '[JSON] (RespondEmpty 202 "OK")
           )
    :<|> Named "get-team-name" ("name" :> CanThrow 'TeamNotFound :> Get '[JSON] TeamName)
    :<|> Named
           "update-team-status"
           ( "status"
               :> CanThrow 'TeamNotFound
               :> CanThrow 'InvalidTeamStatusUpdate
               :> ReqBody '[JSON] TeamStatusUpdate
               :> MultiVerb1 'PUT '[JSON] (RespondEmpty 200 "OK")
           )
    :<|> "members"
      :> ( Named
             "unchecked-add-team-member"
             ( CanThrow 'TooManyTeamMembers
                 :> CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                 :> CanThrow 'TooManyTeamAdmins
                 :> ReqBody '[JSON] NewTeamMember
                 :> MultiVerb1 'POST '[JSON] (RespondEmpty 200 "OK")
             )
             :<|> Named
                    "unchecked-get-team-members"
                    ( QueryParam' '[Strict] "maxResults" (Range 1 HardTruncationLimit Int32)
                        :> Get '[JSON] TeamMemberList
                    )
             :<|> Named
                    "unchecked-get-team-member"
                    ( Capture "uid" UserId
                        :> CanThrow 'TeamMemberNotFound
                        :> Get '[JSON] TeamMember
                    )
             :<|> Named
                    "can-user-join-team"
                    ( "check"
                        :> CanThrow 'TooManyTeamMembersOnTeamWithLegalhold
                        :> MultiVerb1 'GET '[JSON] (RespondEmpty 200 "User can join")
                    )
             :<|> Named
                    "unchecked-update-team-member"
                    ( CanThrow 'AccessDenied
                        :> CanThrow 'InvalidPermissions
                        :> CanThrow 'TeamNotFound
                        :> CanThrow 'TeamMemberNotFound
                        :> CanThrow 'TooManyTeamAdmins
                        :> CanThrow 'NotATeamMember
                        :> CanThrow OperationDenied
                        :> ReqBody '[JSON] NewTeamMember
                        :> MultiVerb1 'PUT '[JSON] (RespondEmpty 200 "")
                    )
         )
    :<|> Named
           "user-is-team-owner"
           ( "is-team-owner"
               :> Capture "uid" UserId
               :> CanThrow 'AccessDenied
               :> CanThrow 'TeamMemberNotFound
               :> CanThrow 'NotATeamMember
               :> MultiVerb1 'GET '[JSON] (RespondEmpty 200 "User is team owner")
           )
    :<|> "search-visibility"
      :> ( Named "get-search-visibility-internal" (Get '[JSON] TeamSearchVisibilityView)
             :<|> Named
                    "set-search-visibility-internal"
                    ( CanThrow 'TeamSearchVisibilityNotEnabled
                        :> CanThrow OperationDenied
                        :> CanThrow 'NotATeamMember
                        :> CanThrow 'TeamNotFound
                        :> ReqBody '[JSON] TeamSearchVisibilityView
                        :> MultiVerb1 'PUT '[JSON] (RespondEmpty 204 "OK")
                    )
         )

type IFeatureStatusGet cfg =
  Named
    '("iget", cfg)
    ( Description (FeatureAPIDesc cfg)
        :> FeatureStatusBaseGet cfg
    )

type IFeatureStatusPut cfg =
  Named
    '("iput", cfg)
    ( Description (FeatureAPIDesc cfg)
        :> FeatureStatusBasePutInternal cfg
    )

type IFeatureStatusPatch cfg =
  Named
    '("ipatch", cfg)
    ( Description (FeatureAPIDesc cfg)
        :> FeatureStatusBasePatchInternal cfg
    )

type FeatureStatusBasePutInternal cfg =
  FeatureStatusBaseInternal
    (AppendSymbol "Put config for " (FeatureSymbol cfg))
    cfg
    ( ReqBody '[JSON] (Feature cfg)
        :> Put '[JSON] (LockableFeature cfg)
    )

type FeatureStatusBasePatchInternal cfg =
  FeatureStatusBaseInternal
    (AppendSymbol "Patch config for " (FeatureSymbol cfg))
    cfg
    ( ReqBody '[JSON] (LockableFeaturePatch cfg)
        :> Patch '[JSON] (LockableFeature cfg)
    )

type FeatureStatusBaseInternal desc cfg a =
  Summary desc
    :> CanThrow OperationDenied
    :> CanThrow 'NotATeamMember
    :> CanThrow 'TeamNotFound
    :> CanThrow TeamFeatureError
    :> CanThrowMany (FeatureErrors cfg)
    :> "teams"
    :> Capture "tid" TeamId
    :> "features"
    :> FeatureSymbol cfg
    :> a

type IFeatureStatusLockStatusPut cfg =
  Named
    '("ilock", cfg)
    ( Summary (AppendSymbol "(Un-)lock " (FeatureSymbol cfg))
        :> Description (FeatureAPIDesc cfg)
        :> CanThrow 'NotATeamMember
        :> CanThrow 'TeamNotFound
        :> "teams"
        :> Capture "tid" TeamId
        :> "features"
        :> FeatureSymbol cfg
        :> Capture "lockStatus" LockStatus
        :> Put '[JSON] LockStatusResponse
    )

type FeatureNoConfigMultiGetBase featureName =
  Summary
    (AppendSymbol "Get team feature status in bulk for feature " (FeatureSymbol featureName))
    :> "features-multi-teams"
    :> FeatureSymbol featureName
    :> ReqBody '[JSON] TeamFeatureNoConfigMultiRequest
    :> Post '[JSON] (TeamFeatureNoConfigMultiResponse featureName)

type IFeatureNoConfigMultiGet f =
  Named
    '("igetmulti", f)
    (FeatureNoConfigMultiGetBase f)

type IFederationAPI =
  Named
    "get-federation-status"
    ( Summary "Get the federation status (only needed for integration/QA tests at the time of writing it)"
        :> CanThrow UnreachableBackends
        :> ZLocalUser
        :> "federation-status"
        :> ReqBody '[JSON] RemoteDomains
        :> Get '[JSON] FederationStatus
    )

type IConversationAPI =
  Named
    "conversation-get-member"
    ( "conversations"
        :> Capture "cnv" ConvId
        :> "members"
        :> Capture "usr" UserId
        :> Get '[JSON] (Maybe Member)
    )
    -- This endpoint can lead to the following events being sent:
    -- - MemberJoin event to you, if the conversation existed and had < 2 members before
    -- - MemberJoin event to other, if the conversation existed and only the other was member
    --   before
    :<|> Named
           "conversation-accept-v2"
           ( CanThrow 'InvalidOperation
               :> CanThrow 'ConvNotFound
               :> ZLocalUser
               :> ZOptConn
               :> "conversations"
               :> Capture "cnv" ConvId
               :> "accept"
               :> "v2"
               :> Put '[JSON] Conversation
           )
    :<|> Named
           "conversation-block-unqualified"
           ( CanThrow 'InvalidOperation
               :> CanThrow 'ConvNotFound
               :> ZUser
               :> "conversations"
               :> Capture "cnv" ConvId
               :> "block"
               :> Put '[JSON] ()
           )
    :<|> Named
           "conversation-block"
           ( CanThrow 'InvalidOperation
               :> CanThrow 'ConvNotFound
               :> ZLocalUser
               :> "conversations"
               :> QualifiedCapture "cnv" ConvId
               :> "block"
               :> Put '[JSON] ()
           )
    -- This endpoint can lead to the following events being sent:
    -- - MemberJoin event to you, if the conversation existed and had < 2 members before
    -- - MemberJoin event to other, if the conversation existed and only the other was member
    --   before
    :<|> Named
           "conversation-unblock-unqualified"
           ( CanThrow 'InvalidOperation
               :> CanThrow 'ConvNotFound
               :> ZLocalUser
               :> ZOptConn
               :> "conversations"
               :> Capture "cnv" ConvId
               :> "unblock"
               :> Put '[JSON] Conversation
           )
    -- This endpoint can lead to the following events being sent:
    -- - MemberJoin event to you, if the conversation existed and had < 2 members before
    -- - MemberJoin event to other, if the conversation existed and only the other was member
    --   before
    :<|> Named
           "conversation-unblock"
           ( CanThrow 'InvalidOperation
               :> CanThrow 'ConvNotFound
               :> ZLocalUser
               :> ZOptConn
               :> "conversations"
               :> QualifiedCapture "cnv" ConvId
               :> "unblock"
               :> Put '[JSON] ()
           )
    :<|> Named
           "conversation-meta"
           ( CanThrow 'ConvNotFound
               :> "conversations"
               :> Capture "cnv" ConvId
               :> "meta"
               :> Get '[JSON] ConversationMetadata
           )
    :<|> Named
           "conversation-mls-one-to-one"
           ( CanThrow 'NotConnected
               :> CanThrow 'MLSNotEnabled
               :> "conversations"
               :> "mls-one2one"
               :> ZLocalUser
               :> QualifiedCapture "user" UserId
               :> Get '[JSON] Conversation
           )
    :<|> Named
           "conversation-mls-one-to-one-established"
           ( CanThrow 'NotConnected
               :> CanThrow 'MLSNotEnabled
               :> ZLocalUser
               :> "conversations"
               :> "mls-one2one"
               :> QualifiedCapture "user" UserId
               :> "established"
               :> Get '[JSON] Bool
           )

type IMiscAPI =
  Named
    "get-team-members"
    ( CanThrow 'NonBindingTeam
        :> CanThrow 'TeamNotFound
        :> "users"
        :> Capture "uid" UserId
        :> "team"
        :> "members"
        :> Get '[JSON] TeamMemberList
    )
    :<|> Named
           "get-team-id"
           ( CanThrow 'NonBindingTeam
               :> CanThrow 'TeamNotFound
               :> "users"
               :> Capture "uid" UserId
               :> "team"
               :> Get '[JSON] TeamId
           )
    :<|> Named
           "test-get-clients"
           ( -- eg. https://github.com/wireapp/wire-server/blob/3bdca5fc8154e324773802a0deb46d884bd09143/services/brig/test/integration/API/User/Client.hs#L319
             "test"
               :> "clients"
               :> ZUser
               :> Get '[JSON] [ClientId]
           )
    :<|> Named
           "test-add-client"
           ( "clients"
               :> ZUser
               :> Capture "cid" ClientId
               :> MultiVerb1
                    'POST
                    '[JSON]
                    (RespondEmpty 200 "OK")
           )
    :<|> Named
           "test-delete-client"
           ( "clients"
               :> ZUser
               :> Capture "cid" ClientId
               :> MultiVerb1
                    'DELETE
                    '[JSON]
                    (RespondEmpty 200 "OK")
           )
    :<|> Named
           "add-service"
           ( "services"
               :> ReqBody '[JSON] Service
               :> MultiVerb1
                    'POST
                    '[JSON]
                    (RespondEmpty 200 "OK")
           )
    :<|> Named
           "delete-service"
           ( "services"
               :> ReqBody '[JSON] ServiceRef
               :> MultiVerb1
                    'DELETE
                    '[JSON]
                    (RespondEmpty 200 "OK")
           )
    :<|> Named
           "i-add-bot"
           ( -- This endpoint can lead to the following events being sent:
             -- - MemberJoin event to members
             CanThrow ('ActionDenied 'AddConversationMember)
               :> CanThrow 'ConvNotFound
               :> CanThrow 'InvalidOperation
               :> CanThrow 'TooManyMembers
               :> "bots"
               :> ZLocalUser
               :> ZConn
               :> ReqBody '[JSON] AddBot
               :> Post '[JSON] Event
           )
    :<|> Named
           "delete-bot"
           ( -- This endpoint can lead to the following events being sent:
             -- - MemberLeave event to members
             CanThrow 'ConvNotFound
               :> CanThrow ('ActionDenied 'RemoveConversationMember)
               :> "bots"
               :> ZLocalUser
               :> ZOptConn
               :> ReqBody '[JSON] RemoveBot
               :> MultiVerb
                    'DELETE
                    '[JSON]
                    (UpdateResponses "Bot not found" "Bot deleted" Event)
                    (UpdateResult Event)
           )
    :<|> Named
           "put-custom-backend"
           ( "custom-backend"
               :> "by-domain"
               :> Capture "domain" Domain
               :> ReqBody '[JSON] CustomBackend
               :> MultiVerb1 'PUT '[JSON] (RespondEmpty 201 "OK")
           )
    :<|> Named
           "delete-custom-backend"
           ( "custom-backend"
               :> "by-domain"
               :> Capture "domain" Domain
               :> MultiVerb1 'DELETE '[JSON] (RespondEmpty 200 "OK")
           )

type IEJPDAPI =
  Named
    "get-conversations-by-user"
    ( CanThrow 'NotConnected
        :> "user"
        :> Capture "user" UserId
        :> "all-conversations"
        :> Get '[Servant.JSON] [EJPDConvInfo]
    )

swaggerDoc :: OpenApi
swaggerDoc :: OpenApi
swaggerDoc =
  Proxy
  ("i"
   :> (Named
         "status"
         ("status" :> MultiVerb 'GET '[JSON] '[RespondEmpty 200 "OK"] ())
       :<|> (Named
               "delete-user"
               (Summary
                  "Remove a user from their teams and conversations and erase their clients"
                :> (ZLocalUser
                    :> (ZOptConn
                        :> ("user"
                            :> MultiVerb
                                 'DELETE
                                 '[JSON]
                                 '[RespondEmpty 200 "Remove a user from Galley"]
                                 ()))))
             :<|> (Named
                     "connect"
                     (Summary "Create a connect conversation (deprecated)"
                      :> (CanThrow 'ConvNotFound
                          :> (CanThrow 'InvalidOperation
                              :> (CanThrow 'NotConnected
                                  :> (CanThrow UnreachableBackends
                                      :> (ZLocalUser
                                          :> (ZOptConn
                                              :> ("conversations"
                                                  :> ("connect"
                                                      :> (ReqBody '[JSON] Connect
                                                          :> MultiVerb
                                                               'POST
                                                               '[JSON]
                                                               '[WithHeaders
                                                                   ConversationHeaders
                                                                   Conversation
                                                                   (VersionedRespond
                                                                      'V6
                                                                      200
                                                                      "Conversation existed"
                                                                      Conversation),
                                                                 WithHeaders
                                                                   ConversationHeaders
                                                                   Conversation
                                                                   (VersionedRespond
                                                                      'V6
                                                                      201
                                                                      "Conversation created"
                                                                      Conversation)]
                                                               (ResponseForExistedCreated
                                                                  Conversation)))))))))))
                   :<|> (Named
                           "get-conversation-clients"
                           (Summary "Get mls conversation client list"
                            :> (CanThrow 'ConvNotFound
                                :> ("group"
                                    :> (Capture "gid" GroupId
                                        :> MultiVerb
                                             'GET
                                             '[JSON]
                                             '[Respond 200 "Clients" ClientList]
                                             ClientList))))
                         :<|> (Named
                                 "guard-legalhold-policy-conflicts"
                                 ("guard-legalhold-policy-conflicts"
                                  :> (CanThrow 'MissingLegalholdConsent
                                      :> (CanThrow 'MissingLegalholdConsentOldClients
                                          :> (ReqBody '[JSON] GuardLegalholdPolicyConflicts
                                              :> MultiVerb
                                                   'PUT
                                                   '[JSON]
                                                   '[RespondEmpty 200 "Guard Legalhold Policy"]
                                                   ()))))
                               :<|> (("legalhold"
                                      :> ("whitelisted-teams"
                                          :> (Capture "tid" TeamId
                                              :> (Named
                                                    "set-team-legalhold-whitelisted"
                                                    (MultiVerb
                                                       'PUT
                                                       '[JSON]
                                                       '[RespondEmpty
                                                           200 "Team Legalhold Whitelisted"]
                                                       ())
                                                  :<|> (Named
                                                          "unset-team-legalhold-whitelisted"
                                                          (MultiVerb
                                                             'DELETE
                                                             '[JSON]
                                                             '[RespondEmpty
                                                                 204
                                                                 "Team Legalhold un-Whitelisted"]
                                                             ())
                                                        :<|> Named
                                                               "get-team-legalhold-whitelisted"
                                                               (MultiVerb
                                                                  'GET
                                                                  '[JSON]
                                                                  '[RespondEmpty
                                                                      404
                                                                      "Team not Legalhold Whitelisted",
                                                                    RespondEmpty
                                                                      200
                                                                      "Team Legalhold Whitelisted"]
                                                                  Bool))))))
                                     :<|> (("teams"
                                            :> (Capture "tid" TeamId
                                                :> (Named
                                                      "get-team-internal"
                                                      (CanThrow 'TeamNotFound
                                                       :> Get '[JSON] TeamData)
                                                    :<|> (Named
                                                            "create-binding-team"
                                                            (ZUser
                                                             :> (ReqBody '[JSON] NewTeam
                                                                 :> MultiVerb
                                                                      'PUT
                                                                      '[JSON]
                                                                      '[WithHeaders
                                                                          '[Header
                                                                              "Location" TeamId]
                                                                          TeamId
                                                                          (RespondEmpty 201 "OK")]
                                                                      TeamId))
                                                          :<|> (Named
                                                                  "delete-binding-team"
                                                                  (CanThrow 'NoBindingTeam
                                                                   :> (CanThrow 'NotAOneMemberTeam
                                                                       :> (CanThrow 'DeleteQueueFull
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (QueryFlag "force"
                                                                                   :> MultiVerb
                                                                                        'DELETE
                                                                                        '[JSON]
                                                                                        '[RespondEmpty
                                                                                            202
                                                                                            "OK"]
                                                                                        ())))))
                                                                :<|> (Named
                                                                        "get-team-name"
                                                                        ("name"
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> Get
                                                                                  '[JSON] TeamName))
                                                                      :<|> (Named
                                                                              "update-team-status"
                                                                              ("status"
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> (CanThrow
                                                                                         'InvalidTeamStatusUpdate
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             TeamStatusUpdate
                                                                                           :> MultiVerb
                                                                                                'PUT
                                                                                                '[JSON]
                                                                                                '[RespondEmpty
                                                                                                    200
                                                                                                    "OK"]
                                                                                                ()))))
                                                                            :<|> (("members"
                                                                                   :> (Named
                                                                                         "unchecked-add-team-member"
                                                                                         (CanThrow
                                                                                            'TooManyTeamMembers
                                                                                          :> (CanThrow
                                                                                                'TooManyTeamMembersOnTeamWithLegalhold
                                                                                              :> (CanThrow
                                                                                                    'TooManyTeamAdmins
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        NewTeamMember
                                                                                                      :> MultiVerb
                                                                                                           'POST
                                                                                                           '[JSON]
                                                                                                           '[RespondEmpty
                                                                                                               200
                                                                                                               "OK"]
                                                                                                           ()))))
                                                                                       :<|> (Named
                                                                                               "unchecked-get-team-members"
                                                                                               (QueryParam'
                                                                                                  '[Strict]
                                                                                                  "maxResults"
                                                                                                  (Range
                                                                                                     1
                                                                                                     HardTruncationLimit
                                                                                                     Int32)
                                                                                                :> Get
                                                                                                     '[JSON]
                                                                                                     TeamMemberList)
                                                                                             :<|> (Named
                                                                                                     "unchecked-get-team-member"
                                                                                                     (Capture
                                                                                                        "uid"
                                                                                                        UserId
                                                                                                      :> (CanThrow
                                                                                                            'TeamMemberNotFound
                                                                                                          :> Get
                                                                                                               '[JSON]
                                                                                                               TeamMember))
                                                                                                   :<|> (Named
                                                                                                           "can-user-join-team"
                                                                                                           ("check"
                                                                                                            :> (CanThrow
                                                                                                                  'TooManyTeamMembersOnTeamWithLegalhold
                                                                                                                :> MultiVerb
                                                                                                                     'GET
                                                                                                                     '[JSON]
                                                                                                                     '[RespondEmpty
                                                                                                                         200
                                                                                                                         "User can join"]
                                                                                                                     ()))
                                                                                                         :<|> Named
                                                                                                                "unchecked-update-team-member"
                                                                                                                (CanThrow
                                                                                                                   'AccessDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'InvalidPermissions
                                                                                                                     :> (CanThrow
                                                                                                                           'TeamNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'TeamMemberNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   'TooManyTeamAdmins
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               NewTeamMember
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'PUT
                                                                                                                                                  '[JSON]
                                                                                                                                                  '[RespondEmpty
                                                                                                                                                      200
                                                                                                                                                      ""]
                                                                                                                                                  ())))))))))))))
                                                                                  :<|> (Named
                                                                                          "user-is-team-owner"
                                                                                          ("is-team-owner"
                                                                                           :> (Capture
                                                                                                 "uid"
                                                                                                 UserId
                                                                                               :> (CanThrow
                                                                                                     'AccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'TeamMemberNotFound
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> MultiVerb
                                                                                                                'GET
                                                                                                                '[JSON]
                                                                                                                '[RespondEmpty
                                                                                                                    200
                                                                                                                    "User is team owner"]
                                                                                                                ())))))
                                                                                        :<|> ("search-visibility"
                                                                                              :> (Named
                                                                                                    "get-search-visibility-internal"
                                                                                                    (Get
                                                                                                       '[JSON]
                                                                                                       TeamSearchVisibilityView)
                                                                                                  :<|> Named
                                                                                                         "set-search-visibility-internal"
                                                                                                         (CanThrow
                                                                                                            'TeamSearchVisibilityNotEnabled
                                                                                                          :> (CanThrow
                                                                                                                OperationDenied
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (ReqBody
                                                                                                                            '[JSON]
                                                                                                                            TeamSearchVisibilityView
                                                                                                                          :> MultiVerb
                                                                                                                               'PUT
                                                                                                                               '[JSON]
                                                                                                                               '[RespondEmpty
                                                                                                                                   204
                                                                                                                                   "OK"]
                                                                                                                               ()))))))))))))))))
                                           :<|> ((Named
                                                    "get-team-members"
                                                    (CanThrow 'NonBindingTeam
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("users"
                                                             :> (Capture "uid" UserId
                                                                 :> ("team"
                                                                     :> ("members"
                                                                         :> Get
                                                                              '[JSON]
                                                                              TeamMemberList))))))
                                                  :<|> (Named
                                                          "get-team-id"
                                                          (CanThrow 'NonBindingTeam
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("users"
                                                                   :> (Capture "uid" UserId
                                                                       :> ("team"
                                                                           :> Get
                                                                                '[JSON] TeamId)))))
                                                        :<|> (Named
                                                                "test-get-clients"
                                                                ("test"
                                                                 :> ("clients"
                                                                     :> (ZUser
                                                                         :> Get
                                                                              '[JSON] [ClientId])))
                                                              :<|> (Named
                                                                      "test-add-client"
                                                                      ("clients"
                                                                       :> (ZUser
                                                                           :> (Capture
                                                                                 "cid" ClientId
                                                                               :> MultiVerb
                                                                                    'POST
                                                                                    '[JSON]
                                                                                    '[RespondEmpty
                                                                                        200 "OK"]
                                                                                    ())))
                                                                    :<|> (Named
                                                                            "test-delete-client"
                                                                            ("clients"
                                                                             :> (ZUser
                                                                                 :> (Capture
                                                                                       "cid"
                                                                                       ClientId
                                                                                     :> MultiVerb
                                                                                          'DELETE
                                                                                          '[JSON]
                                                                                          '[RespondEmpty
                                                                                              200
                                                                                              "OK"]
                                                                                          ())))
                                                                          :<|> (Named
                                                                                  "add-service"
                                                                                  ("services"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         Service
                                                                                       :> MultiVerb
                                                                                            'POST
                                                                                            '[JSON]
                                                                                            '[RespondEmpty
                                                                                                200
                                                                                                "OK"]
                                                                                            ()))
                                                                                :<|> (Named
                                                                                        "delete-service"
                                                                                        ("services"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               ServiceRef
                                                                                             :> MultiVerb
                                                                                                  'DELETE
                                                                                                  '[JSON]
                                                                                                  '[RespondEmpty
                                                                                                      200
                                                                                                      "OK"]
                                                                                                  ()))
                                                                                      :<|> (Named
                                                                                              "i-add-bot"
                                                                                              (CanThrow
                                                                                                 ('ActionDenied
                                                                                                    'AddConversationMember)
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'InvalidOperation
                                                                                                       :> (CanThrow
                                                                                                             'TooManyMembers
                                                                                                           :> ("bots"
                                                                                                               :> (ZLocalUser
                                                                                                                   :> (ZConn
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             AddBot
                                                                                                                           :> Post
                                                                                                                                '[JSON]
                                                                                                                                Event))))))))
                                                                                            :<|> (Named
                                                                                                    "delete-bot"
                                                                                                    (CanThrow
                                                                                                       'ConvNotFound
                                                                                                     :> (CanThrow
                                                                                                           ('ActionDenied
                                                                                                              'RemoveConversationMember)
                                                                                                         :> ("bots"
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (ZOptConn
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           RemoveBot
                                                                                                                         :> MultiVerb
                                                                                                                              'DELETE
                                                                                                                              '[JSON]
                                                                                                                              (UpdateResponses
                                                                                                                                 "Bot not found"
                                                                                                                                 "Bot deleted"
                                                                                                                                 Event)
                                                                                                                              (UpdateResult
                                                                                                                                 Event)))))))
                                                                                                  :<|> (Named
                                                                                                          "put-custom-backend"
                                                                                                          ("custom-backend"
                                                                                                           :> ("by-domain"
                                                                                                               :> (Capture
                                                                                                                     "domain"
                                                                                                                     Domain
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         CustomBackend
                                                                                                                       :> MultiVerb
                                                                                                                            'PUT
                                                                                                                            '[JSON]
                                                                                                                            '[RespondEmpty
                                                                                                                                201
                                                                                                                                "OK"]
                                                                                                                            ()))))
                                                                                                        :<|> Named
                                                                                                               "delete-custom-backend"
                                                                                                               ("custom-backend"
                                                                                                                :> ("by-domain"
                                                                                                                    :> (Capture
                                                                                                                          "domain"
                                                                                                                          Domain
                                                                                                                        :> MultiVerb
                                                                                                                             'DELETE
                                                                                                                             '[JSON]
                                                                                                                             '[RespondEmpty
                                                                                                                                 200
                                                                                                                                 "OK"]
                                                                                                                             ())))))))))))))
                                                 :<|> (Named
                                                         "upsert-one2one"
                                                         (Summary
                                                            "Create or Update a connect or one2one conversation."
                                                          :> ("conversations"
                                                              :> ("one2one"
                                                                  :> ("upsert"
                                                                      :> (ReqBody
                                                                            '[JSON]
                                                                            UpsertOne2OneConversationRequest
                                                                          :> MultiVerb
                                                                               'POST
                                                                               '[JSON]
                                                                               '[RespondEmpty
                                                                                   200
                                                                                   "Upsert One2One Policy"]
                                                                               ())))))
                                                       :<|> ((((Named
                                                                  '("iget", LegalholdConfig)
                                                                  (Description ""
                                                                   :> (Summary
                                                                         "Get config for legalhold"
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("legalhold"
                                                                                                   :> Get
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           LegalholdConfig))))))))))
                                                                :<|> (Named
                                                                        '("iput", LegalholdConfig)
                                                                        (Description ""
                                                                         :> (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
                                                                             '("ipatch",
                                                                               LegalholdConfig)
                                                                             (Description ""
                                                                              :> (Summary
                                                                                    "Patch 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]
                                                                                                                            (LockableFeaturePatch
                                                                                                                               LegalholdConfig)
                                                                                                                          :> Patch
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  LegalholdConfig)))))))))))))))
                                                               :<|> ((Named
                                                                        '("iget", SSOConfig)
                                                                        (Description ""
                                                                         :> (Summary
                                                                               "Get config for sso"
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("sso"
                                                                                                         :> Get
                                                                                                              '[JSON]
                                                                                                              (LockableFeature
                                                                                                                 SSOConfig))))))))))
                                                                      :<|> (Named
                                                                              '("iput", SSOConfig)
                                                                              (Description ""
                                                                               :> (Summary
                                                                                     "Put config for sso"
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> (CanThrow
                                                                                                     TeamFeatureError
                                                                                                   :> (CanThrowMany
                                                                                                         '[]
                                                                                                       :> ("teams"
                                                                                                           :> (Capture
                                                                                                                 "tid"
                                                                                                                 TeamId
                                                                                                               :> ("features"
                                                                                                                   :> ("sso"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             (Feature
                                                                                                                                SSOConfig)
                                                                                                                           :> Put
                                                                                                                                '[JSON]
                                                                                                                                (LockableFeature
                                                                                                                                   SSOConfig)))))))))))))
                                                                            :<|> Named
                                                                                   '("ipatch",
                                                                                     SSOConfig)
                                                                                   (Description ""
                                                                                    :> (Summary
                                                                                          "Patch config for sso"
                                                                                        :> (CanThrow
                                                                                              OperationDenied
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> (CanThrow
                                                                                                          TeamFeatureError
                                                                                                        :> (CanThrowMany
                                                                                                              '[]
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("sso"
                                                                                                                            :> (ReqBody
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeaturePatch
                                                                                                                                     SSOConfig)
                                                                                                                                :> Patch
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        SSOConfig)))))))))))))))
                                                                     :<|> ((Named
                                                                              '("iget",
                                                                                SearchVisibilityAvailableConfig)
                                                                              (Description ""
                                                                               :> (Summary
                                                                                     "Get config for searchVisibility"
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("searchVisibility"
                                                                                                               :> Get
                                                                                                                    '[JSON]
                                                                                                                    (LockableFeature
                                                                                                                       SearchVisibilityAvailableConfig))))))))))
                                                                            :<|> (Named
                                                                                    '("iput",
                                                                                      SearchVisibilityAvailableConfig)
                                                                                    (Description ""
                                                                                     :> (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
                                                                                         '("ipatch",
                                                                                           SearchVisibilityAvailableConfig)
                                                                                         (Description
                                                                                            ""
                                                                                          :> (Summary
                                                                                                "Patch config for searchVisibility"
                                                                                              :> (CanThrow
                                                                                                    OperationDenied
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> (CanThrow
                                                                                                                TeamFeatureError
                                                                                                              :> (CanThrowMany
                                                                                                                    '[]
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("searchVisibility"
                                                                                                                                  :> (ReqBody
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeaturePatch
                                                                                                                                           SearchVisibilityAvailableConfig)
                                                                                                                                      :> Patch
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              SearchVisibilityAvailableConfig)))))))))))))))
                                                                           :<|> ((Named
                                                                                    '("iget",
                                                                                      SearchVisibilityInboundConfig)
                                                                                    (Description ""
                                                                                     :> (Summary
                                                                                           "Get config for searchVisibilityInbound"
                                                                                         :> (CanThrow
                                                                                               OperationDenied
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'TeamNotFound
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("searchVisibilityInbound"
                                                                                                                     :> Get
                                                                                                                          '[JSON]
                                                                                                                          (LockableFeature
                                                                                                                             SearchVisibilityInboundConfig))))))))))
                                                                                  :<|> (Named
                                                                                          '("iput",
                                                                                            SearchVisibilityInboundConfig)
                                                                                          (Description
                                                                                             ""
                                                                                           :> (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
                                                                                               '("ipatch",
                                                                                                 SearchVisibilityInboundConfig)
                                                                                               (Description
                                                                                                  ""
                                                                                                :> (Summary
                                                                                                      "Patch config for searchVisibilityInbound"
                                                                                                    :> (CanThrow
                                                                                                          OperationDenied
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> (CanThrow
                                                                                                                      TeamFeatureError
                                                                                                                    :> (CanThrowMany
                                                                                                                          '[]
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("searchVisibilityInbound"
                                                                                                                                        :> (ReqBody
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeaturePatch
                                                                                                                                                 SearchVisibilityInboundConfig)
                                                                                                                                            :> Patch
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    SearchVisibilityInboundConfig)))))))))))))))
                                                                                 :<|> ((Named
                                                                                          '("iget",
                                                                                            ValidateSAMLEmailsConfig)
                                                                                          (Description
                                                                                             ""
                                                                                           :> (Summary
                                                                                                 "Get config for validateSAMLemails"
                                                                                               :> (CanThrow
                                                                                                     OperationDenied
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'TeamNotFound
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("validateSAMLemails"
                                                                                                                           :> Get
                                                                                                                                '[JSON]
                                                                                                                                (LockableFeature
                                                                                                                                   ValidateSAMLEmailsConfig))))))))))
                                                                                        :<|> (Named
                                                                                                '("iput",
                                                                                                  ValidateSAMLEmailsConfig)
                                                                                                (Description
                                                                                                   ""
                                                                                                 :> (Summary
                                                                                                       "Put config for validateSAMLemails"
                                                                                                     :> (CanThrow
                                                                                                           OperationDenied
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'TeamNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       TeamFeatureError
                                                                                                                     :> (CanThrowMany
                                                                                                                           '[]
                                                                                                                         :> ("teams"
                                                                                                                             :> (Capture
                                                                                                                                   "tid"
                                                                                                                                   TeamId
                                                                                                                                 :> ("features"
                                                                                                                                     :> ("validateSAMLemails"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               (Feature
                                                                                                                                                  ValidateSAMLEmailsConfig)
                                                                                                                                             :> Put
                                                                                                                                                  '[JSON]
                                                                                                                                                  (LockableFeature
                                                                                                                                                     ValidateSAMLEmailsConfig)))))))))))))
                                                                                              :<|> Named
                                                                                                     '("ipatch",
                                                                                                       ValidateSAMLEmailsConfig)
                                                                                                     (Description
                                                                                                        ""
                                                                                                      :> (Summary
                                                                                                            "Patch config for validateSAMLemails"
                                                                                                          :> (CanThrow
                                                                                                                OperationDenied
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            TeamFeatureError
                                                                                                                          :> (CanThrowMany
                                                                                                                                '[]
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("validateSAMLemails"
                                                                                                                                              :> (ReqBody
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeaturePatch
                                                                                                                                                       ValidateSAMLEmailsConfig)
                                                                                                                                                  :> Patch
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          ValidateSAMLEmailsConfig)))))))))))))))
                                                                                       :<|> ((Named
                                                                                                '("iget",
                                                                                                  DigitalSignaturesConfig)
                                                                                                (Description
                                                                                                   ""
                                                                                                 :> (Summary
                                                                                                       "Get config for digitalSignatures"
                                                                                                     :> (CanThrow
                                                                                                           OperationDenied
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'TeamNotFound
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("digitalSignatures"
                                                                                                                                 :> Get
                                                                                                                                      '[JSON]
                                                                                                                                      (LockableFeature
                                                                                                                                         DigitalSignaturesConfig))))))))))
                                                                                              :<|> (Named
                                                                                                      '("iput",
                                                                                                        DigitalSignaturesConfig)
                                                                                                      (Description
                                                                                                         ""
                                                                                                       :> (Summary
                                                                                                             "Put config for digitalSignatures"
                                                                                                           :> (CanThrow
                                                                                                                 OperationDenied
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'TeamNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             TeamFeatureError
                                                                                                                           :> (CanThrowMany
                                                                                                                                 '[]
                                                                                                                               :> ("teams"
                                                                                                                                   :> (Capture
                                                                                                                                         "tid"
                                                                                                                                         TeamId
                                                                                                                                       :> ("features"
                                                                                                                                           :> ("digitalSignatures"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     (Feature
                                                                                                                                                        DigitalSignaturesConfig)
                                                                                                                                                   :> Put
                                                                                                                                                        '[JSON]
                                                                                                                                                        (LockableFeature
                                                                                                                                                           DigitalSignaturesConfig)))))))))))))
                                                                                                    :<|> Named
                                                                                                           '("ipatch",
                                                                                                             DigitalSignaturesConfig)
                                                                                                           (Description
                                                                                                              ""
                                                                                                            :> (Summary
                                                                                                                  "Patch config for digitalSignatures"
                                                                                                                :> (CanThrow
                                                                                                                      OperationDenied
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  TeamFeatureError
                                                                                                                                :> (CanThrowMany
                                                                                                                                      '[]
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("digitalSignatures"
                                                                                                                                                    :> (ReqBody
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeaturePatch
                                                                                                                                                             DigitalSignaturesConfig)
                                                                                                                                                        :> Patch
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                DigitalSignaturesConfig)))))))))))))))
                                                                                             :<|> ((Named
                                                                                                      '("iget",
                                                                                                        AppLockConfig)
                                                                                                      (Description
                                                                                                         ""
                                                                                                       :> (Summary
                                                                                                             "Get config for appLock"
                                                                                                           :> (CanThrow
                                                                                                                 OperationDenied
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'TeamNotFound
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("appLock"
                                                                                                                                       :> Get
                                                                                                                                            '[JSON]
                                                                                                                                            (LockableFeature
                                                                                                                                               AppLockConfig))))))))))
                                                                                                    :<|> (Named
                                                                                                            '("iput",
                                                                                                              AppLockConfig)
                                                                                                            (Description
                                                                                                               ""
                                                                                                             :> (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
                                                                                                                 '("ipatch",
                                                                                                                   AppLockConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Patch config for appLock"
                                                                                                                      :> (CanThrow
                                                                                                                            OperationDenied
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> (CanThrow
                                                                                                                                        TeamFeatureError
                                                                                                                                      :> (CanThrowMany
                                                                                                                                            '[]
                                                                                                                                          :> ("teams"
                                                                                                                                              :> (Capture
                                                                                                                                                    "tid"
                                                                                                                                                    TeamId
                                                                                                                                                  :> ("features"
                                                                                                                                                      :> ("appLock"
                                                                                                                                                          :> (ReqBody
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeaturePatch
                                                                                                                                                                   AppLockConfig)
                                                                                                                                                              :> Patch
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      AppLockConfig)))))))))))))))
                                                                                                   :<|> ((Named
                                                                                                            '("iget",
                                                                                                              FileSharingConfig)
                                                                                                            (Description
                                                                                                               ""
                                                                                                             :> (Summary
                                                                                                                   "Get config for fileSharing"
                                                                                                                 :> (CanThrow
                                                                                                                       OperationDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               'TeamNotFound
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("fileSharing"
                                                                                                                                             :> Get
                                                                                                                                                  '[JSON]
                                                                                                                                                  (LockableFeature
                                                                                                                                                     FileSharingConfig))))))))))
                                                                                                          :<|> (Named
                                                                                                                  '("iput",
                                                                                                                    FileSharingConfig)
                                                                                                                  (Description
                                                                                                                     ""
                                                                                                                   :> (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
                                                                                                                       '("ipatch",
                                                                                                                         FileSharingConfig)
                                                                                                                       (Description
                                                                                                                          ""
                                                                                                                        :> (Summary
                                                                                                                              "Patch config for fileSharing"
                                                                                                                            :> (CanThrow
                                                                                                                                  OperationDenied
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> (CanThrowMany
                                                                                                                                                  '[]
                                                                                                                                                :> ("teams"
                                                                                                                                                    :> (Capture
                                                                                                                                                          "tid"
                                                                                                                                                          TeamId
                                                                                                                                                        :> ("features"
                                                                                                                                                            :> ("fileSharing"
                                                                                                                                                                :> (ReqBody
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeaturePatch
                                                                                                                                                                         FileSharingConfig)
                                                                                                                                                                    :> Patch
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            FileSharingConfig)))))))))))))))
                                                                                                         :<|> (Named
                                                                                                                 '("iget",
                                                                                                                   ClassifiedDomainsConfig)
                                                                                                                 (Description
                                                                                                                    ""
                                                                                                                  :> (Summary
                                                                                                                        "Get config for classifiedDomains"
                                                                                                                      :> (CanThrow
                                                                                                                            OperationDenied
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("classifiedDomains"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          ClassifiedDomainsConfig))))))))))
                                                                                                               :<|> ((Named
                                                                                                                        '("iget",
                                                                                                                          ConferenceCallingConfig)
                                                                                                                        (Description
                                                                                                                           ""
                                                                                                                         :> (Summary
                                                                                                                               "Get config for conferenceCalling"
                                                                                                                             :> (CanThrow
                                                                                                                                   OperationDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           'TeamNotFound
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("conferenceCalling"
                                                                                                                                                         :> Get
                                                                                                                                                              '[JSON]
                                                                                                                                                              (LockableFeature
                                                                                                                                                                 ConferenceCallingConfig))))))))))
                                                                                                                      :<|> (Named
                                                                                                                              '("iput",
                                                                                                                                ConferenceCallingConfig)
                                                                                                                              (Description
                                                                                                                                 ""
                                                                                                                               :> (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
                                                                                                                                   '("ipatch",
                                                                                                                                     ConferenceCallingConfig)
                                                                                                                                   (Description
                                                                                                                                      ""
                                                                                                                                    :> (Summary
                                                                                                                                          "Patch config for conferenceCalling"
                                                                                                                                        :> (CanThrow
                                                                                                                                              OperationDenied
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          TeamFeatureError
                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                              '[]
                                                                                                                                                            :> ("teams"
                                                                                                                                                                :> (Capture
                                                                                                                                                                      "tid"
                                                                                                                                                                      TeamId
                                                                                                                                                                    :> ("features"
                                                                                                                                                                        :> ("conferenceCalling"
                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeaturePatch
                                                                                                                                                                                     ConferenceCallingConfig)
                                                                                                                                                                                :> Patch
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        ConferenceCallingConfig)))))))))))))))
                                                                                                                     :<|> ((Named
                                                                                                                              '("iget",
                                                                                                                                SelfDeletingMessagesConfig)
                                                                                                                              (Description
                                                                                                                                 ""
                                                                                                                               :> (Summary
                                                                                                                                     "Get config for selfDeletingMessages"
                                                                                                                                   :> (CanThrow
                                                                                                                                         OperationDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'TeamNotFound
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("selfDeletingMessages"
                                                                                                                                                               :> Get
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    (LockableFeature
                                                                                                                                                                       SelfDeletingMessagesConfig))))))))))
                                                                                                                            :<|> (Named
                                                                                                                                    '("iput",
                                                                                                                                      SelfDeletingMessagesConfig)
                                                                                                                                    (Description
                                                                                                                                       ""
                                                                                                                                     :> (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
                                                                                                                                         '("ipatch",
                                                                                                                                           SelfDeletingMessagesConfig)
                                                                                                                                         (Description
                                                                                                                                            ""
                                                                                                                                          :> (Summary
                                                                                                                                                "Patch config for selfDeletingMessages"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    OperationDenied
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                TeamFeatureError
                                                                                                                                                              :> (CanThrowMany
                                                                                                                                                                    '[]
                                                                                                                                                                  :> ("teams"
                                                                                                                                                                      :> (Capture
                                                                                                                                                                            "tid"
                                                                                                                                                                            TeamId
                                                                                                                                                                          :> ("features"
                                                                                                                                                                              :> ("selfDeletingMessages"
                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeaturePatch
                                                                                                                                                                                           SelfDeletingMessagesConfig)
                                                                                                                                                                                      :> Patch
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              SelfDeletingMessagesConfig)))))))))))))))
                                                                                                                           :<|> ((Named
                                                                                                                                    '("iget",
                                                                                                                                      GuestLinksConfig)
                                                                                                                                    (Description
                                                                                                                                       ""
                                                                                                                                     :> (Summary
                                                                                                                                           "Get config for conversationGuestLinks"
                                                                                                                                         :> (CanThrow
                                                                                                                                               OperationDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'TeamNotFound
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("conversationGuestLinks"
                                                                                                                                                                     :> Get
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          (LockableFeature
                                                                                                                                                                             GuestLinksConfig))))))))))
                                                                                                                                  :<|> (Named
                                                                                                                                          '("iput",
                                                                                                                                            GuestLinksConfig)
                                                                                                                                          (Description
                                                                                                                                             ""
                                                                                                                                           :> (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
                                                                                                                                               '("ipatch",
                                                                                                                                                 GuestLinksConfig)
                                                                                                                                               (Description
                                                                                                                                                  ""
                                                                                                                                                :> (Summary
                                                                                                                                                      "Patch config for conversationGuestLinks"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          OperationDenied
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      TeamFeatureError
                                                                                                                                                                    :> (CanThrowMany
                                                                                                                                                                          '[]
                                                                                                                                                                        :> ("teams"
                                                                                                                                                                            :> (Capture
                                                                                                                                                                                  "tid"
                                                                                                                                                                                  TeamId
                                                                                                                                                                                :> ("features"
                                                                                                                                                                                    :> ("conversationGuestLinks"
                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeaturePatch
                                                                                                                                                                                                 GuestLinksConfig)
                                                                                                                                                                                            :> Patch
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    GuestLinksConfig)))))))))))))))
                                                                                                                                 :<|> ((Named
                                                                                                                                          '("iget",
                                                                                                                                            SndFactorPasswordChallengeConfig)
                                                                                                                                          (Description
                                                                                                                                             ""
                                                                                                                                           :> (Summary
                                                                                                                                                 "Get config for sndFactorPasswordChallenge"
                                                                                                                                               :> (CanThrow
                                                                                                                                                     OperationDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'TeamNotFound
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("sndFactorPasswordChallenge"
                                                                                                                                                                           :> Get
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                   SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                        :<|> (Named
                                                                                                                                                '("iput",
                                                                                                                                                  SndFactorPasswordChallengeConfig)
                                                                                                                                                (Description
                                                                                                                                                   ""
                                                                                                                                                 :> (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
                                                                                                                                                     '("ipatch",
                                                                                                                                                       SndFactorPasswordChallengeConfig)
                                                                                                                                                     (Description
                                                                                                                                                        ""
                                                                                                                                                      :> (Summary
                                                                                                                                                            "Patch config for sndFactorPasswordChallenge"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                OperationDenied
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            TeamFeatureError
                                                                                                                                                                          :> (CanThrowMany
                                                                                                                                                                                '[]
                                                                                                                                                                              :> ("teams"
                                                                                                                                                                                  :> (Capture
                                                                                                                                                                                        "tid"
                                                                                                                                                                                        TeamId
                                                                                                                                                                                      :> ("features"
                                                                                                                                                                                          :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeaturePatch
                                                                                                                                                                                                       SndFactorPasswordChallengeConfig)
                                                                                                                                                                                                  :> Patch
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                          SndFactorPasswordChallengeConfig)))))))))))))))
                                                                                                                                       :<|> ((Named
                                                                                                                                                '("iget",
                                                                                                                                                  MLSConfig)
                                                                                                                                                (Description
                                                                                                                                                   ""
                                                                                                                                                 :> (Summary
                                                                                                                                                       "Get config for mls"
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           OperationDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("mls"
                                                                                                                                                                                 :> Get
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                         MLSConfig))))))))))
                                                                                                                                              :<|> (Named
                                                                                                                                                      '("iput",
                                                                                                                                                        MLSConfig)
                                                                                                                                                      (Description
                                                                                                                                                         ""
                                                                                                                                                       :> (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
                                                                                                                                                           '("ipatch",
                                                                                                                                                             MLSConfig)
                                                                                                                                                           (Description
                                                                                                                                                              ""
                                                                                                                                                            :> (Summary
                                                                                                                                                                  "Patch config for mls"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      OperationDenied
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  TeamFeatureError
                                                                                                                                                                                :> (CanThrowMany
                                                                                                                                                                                      '[]
                                                                                                                                                                                    :> ("teams"
                                                                                                                                                                                        :> (Capture
                                                                                                                                                                                              "tid"
                                                                                                                                                                                              TeamId
                                                                                                                                                                                            :> ("features"
                                                                                                                                                                                                :> ("mls"
                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeaturePatch
                                                                                                                                                                                                             MLSConfig)
                                                                                                                                                                                                        :> Patch
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                                                MLSConfig)))))))))))))))
                                                                                                                                             :<|> ((Named
                                                                                                                                                      '("iget",
                                                                                                                                                        ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                      (Description
                                                                                                                                                         ""
                                                                                                                                                       :> (Summary
                                                                                                                                                             "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 OperationDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                                       :> Get
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                               ExposeInvitationURLsToTeamAdminConfig))))))))))
                                                                                                                                                    :<|> (Named
                                                                                                                                                            '("iput",
                                                                                                                                                              ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                            (Description
                                                                                                                                                               ""
                                                                                                                                                             :> (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
                                                                                                                                                                 '("ipatch",
                                                                                                                                                                   ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                 (Description
                                                                                                                                                                    ""
                                                                                                                                                                  :> (Summary
                                                                                                                                                                        "Patch config for exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            OperationDenied
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        TeamFeatureError
                                                                                                                                                                                      :> (CanThrowMany
                                                                                                                                                                                            '[]
                                                                                                                                                                                          :> ("teams"
                                                                                                                                                                                              :> (Capture
                                                                                                                                                                                                    "tid"
                                                                                                                                                                                                    TeamId
                                                                                                                                                                                                  :> ("features"
                                                                                                                                                                                                      :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeaturePatch
                                                                                                                                                                                                                   ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                                                                              :> Patch
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   (LockableFeature
                                                                                                                                                                                                                      ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                                                                                   :<|> ((Named
                                                                                                                                                            '("iget",
                                                                                                                                                              OutlookCalIntegrationConfig)
                                                                                                                                                            (Description
                                                                                                                                                               ""
                                                                                                                                                             :> (Summary
                                                                                                                                                                   "Get config for outlookCalIntegration"
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       OperationDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "tid"
                                                                                                                                                                                       TeamId
                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                         :> ("outlookCalIntegration"
                                                                                                                                                                                             :> Get
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                     OutlookCalIntegrationConfig))))))))))
                                                                                                                                                          :<|> (Named
                                                                                                                                                                  '("iput",
                                                                                                                                                                    OutlookCalIntegrationConfig)
                                                                                                                                                                  (Description
                                                                                                                                                                     ""
                                                                                                                                                                   :> (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
                                                                                                                                                                       '("ipatch",
                                                                                                                                                                         OutlookCalIntegrationConfig)
                                                                                                                                                                       (Description
                                                                                                                                                                          ""
                                                                                                                                                                        :> (Summary
                                                                                                                                                                              "Patch config for outlookCalIntegration"
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  OperationDenied
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              TeamFeatureError
                                                                                                                                                                                            :> (CanThrowMany
                                                                                                                                                                                                  '[]
                                                                                                                                                                                                :> ("teams"
                                                                                                                                                                                                    :> (Capture
                                                                                                                                                                                                          "tid"
                                                                                                                                                                                                          TeamId
                                                                                                                                                                                                        :> ("features"
                                                                                                                                                                                                            :> ("outlookCalIntegration"
                                                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (LockableFeaturePatch
                                                                                                                                                                                                                         OutlookCalIntegrationConfig)
                                                                                                                                                                                                                    :> Patch
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         (LockableFeature
                                                                                                                                                                                                                            OutlookCalIntegrationConfig)))))))))))))))
                                                                                                                                                         :<|> ((Named
                                                                                                                                                                  '("iget",
                                                                                                                                                                    MlsE2EIdConfig)
                                                                                                                                                                  (Description
                                                                                                                                                                     ""
                                                                                                                                                                   :> (Summary
                                                                                                                                                                         "Get config for mlsE2EId"
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             OperationDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                   :> ("teams"
                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                             "tid"
                                                                                                                                                                                             TeamId
                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                               :> ("mlsE2EId"
                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                           MlsE2EIdConfig))))))))))
                                                                                                                                                                :<|> (Named
                                                                                                                                                                        '("iput",
                                                                                                                                                                          MlsE2EIdConfig)
                                                                                                                                                                        (Description
                                                                                                                                                                           ""
                                                                                                                                                                         :> (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
                                                                                                                                                                             '("ipatch",
                                                                                                                                                                               MlsE2EIdConfig)
                                                                                                                                                                             (Description
                                                                                                                                                                                ""
                                                                                                                                                                              :> (Summary
                                                                                                                                                                                    "Patch config for mlsE2EId"
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        OperationDenied
                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                    TeamFeatureError
                                                                                                                                                                                                  :> (CanThrowMany
                                                                                                                                                                                                        '[]
                                                                                                                                                                                                      :> ("teams"
                                                                                                                                                                                                          :> (Capture
                                                                                                                                                                                                                "tid"
                                                                                                                                                                                                                TeamId
                                                                                                                                                                                                              :> ("features"
                                                                                                                                                                                                                  :> ("mlsE2EId"
                                                                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (LockableFeaturePatch
                                                                                                                                                                                                                               MlsE2EIdConfig)
                                                                                                                                                                                                                          :> Patch
                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                                                                  MlsE2EIdConfig)))))))))))))))
                                                                                                                                                               :<|> ((Named
                                                                                                                                                                        '("iget",
                                                                                                                                                                          MlsMigrationConfig)
                                                                                                                                                                        (Description
                                                                                                                                                                           ""
                                                                                                                                                                         :> (Summary
                                                                                                                                                                               "Get config for mlsMigration"
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                         :> ("teams"
                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                   "tid"
                                                                                                                                                                                                   TeamId
                                                                                                                                                                                                 :> ("features"
                                                                                                                                                                                                     :> ("mlsMigration"
                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                 MlsMigrationConfig))))))))))
                                                                                                                                                                      :<|> (Named
                                                                                                                                                                              '("iput",
                                                                                                                                                                                MlsMigrationConfig)
                                                                                                                                                                              (Description
                                                                                                                                                                                 ""
                                                                                                                                                                               :> (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
                                                                                                                                                                                   '("ipatch",
                                                                                                                                                                                     MlsMigrationConfig)
                                                                                                                                                                                   (Description
                                                                                                                                                                                      ""
                                                                                                                                                                                    :> (Summary
                                                                                                                                                                                          "Patch config for mlsMigration"
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              OperationDenied
                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                          TeamFeatureError
                                                                                                                                                                                                        :> (CanThrowMany
                                                                                                                                                                                                              '[]
                                                                                                                                                                                                            :> ("teams"
                                                                                                                                                                                                                :> (Capture
                                                                                                                                                                                                                      "tid"
                                                                                                                                                                                                                      TeamId
                                                                                                                                                                                                                    :> ("features"
                                                                                                                                                                                                                        :> ("mlsMigration"
                                                                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (LockableFeaturePatch
                                                                                                                                                                                                                                     MlsMigrationConfig)
                                                                                                                                                                                                                                :> Patch
                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                                                                        MlsMigrationConfig)))))))))))))))
                                                                                                                                                                     :<|> ((Named
                                                                                                                                                                              '("iget",
                                                                                                                                                                                EnforceFileDownloadLocationConfig)
                                                                                                                                                                              (Description
                                                                                                                                                                                 "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                               :> (Summary
                                                                                                                                                                                     "Get config for enforceFileDownloadLocation"
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         OperationDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                               :> ("teams"
                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                         "tid"
                                                                                                                                                                                                         TeamId
                                                                                                                                                                                                       :> ("features"
                                                                                                                                                                                                           :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                                       EnforceFileDownloadLocationConfig))))))))))
                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                    '("iput",
                                                                                                                                                                                      EnforceFileDownloadLocationConfig)
                                                                                                                                                                                    (Description
                                                                                                                                                                                       "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                                     :> (Summary
                                                                                                                                                                                           "Put config for enforceFileDownloadLocation"
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               OperationDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           TeamFeatureError
                                                                                                                                                                                                         :> (CanThrowMany
                                                                                                                                                                                                               '[]
                                                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                                                       "tid"
                                                                                                                                                                                                                       TeamId
                                                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                                                         :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                   (Feature
                                                                                                                                                                                                                                      EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                                                 :> Put
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                                         EnforceFileDownloadLocationConfig)))))))))))))
                                                                                                                                                                                  :<|> Named
                                                                                                                                                                                         '("ipatch",
                                                                                                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                                                                                                         (Description
                                                                                                                                                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                                                          :> (Summary
                                                                                                                                                                                                "Patch config for enforceFileDownloadLocation"
                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                    OperationDenied
                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                            'TeamNotFound
                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                TeamFeatureError
                                                                                                                                                                                                              :> (CanThrowMany
                                                                                                                                                                                                                    '[]
                                                                                                                                                                                                                  :> ("teams"
                                                                                                                                                                                                                      :> (Capture
                                                                                                                                                                                                                            "tid"
                                                                                                                                                                                                                            TeamId
                                                                                                                                                                                                                          :> ("features"
                                                                                                                                                                                                                              :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (LockableFeaturePatch
                                                                                                                                                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                                                      :> Patch
                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                                                                              EnforceFileDownloadLocationConfig)))))))))))))))
                                                                                                                                                                           :<|> (Named
                                                                                                                                                                                   '("iget",
                                                                                                                                                                                     LimitedEventFanoutConfig)
                                                                                                                                                                                   (Description
                                                                                                                                                                                      ""
                                                                                                                                                                                    :> (Summary
                                                                                                                                                                                          "Get config for limitedEventFanout"
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              OperationDenied
                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                                                    :> ("teams"
                                                                                                                                                                                                        :> (Capture
                                                                                                                                                                                                              "tid"
                                                                                                                                                                                                              TeamId
                                                                                                                                                                                                            :> ("features"
                                                                                                                                                                                                                :> ("limitedEventFanout"
                                                                                                                                                                                                                    :> Get
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         (LockableFeature
                                                                                                                                                                                                                            LimitedEventFanoutConfig))))))))))
                                                                                                                                                                                 :<|> (Named
                                                                                                                                                                                         '("iput",
                                                                                                                                                                                           LimitedEventFanoutConfig)
                                                                                                                                                                                         (Description
                                                                                                                                                                                            ""
                                                                                                                                                                                          :> (Summary
                                                                                                                                                                                                "Put config for limitedEventFanout"
                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                    OperationDenied
                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                            'TeamNotFound
                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                TeamFeatureError
                                                                                                                                                                                                              :> (CanThrowMany
                                                                                                                                                                                                                    '[]
                                                                                                                                                                                                                  :> ("teams"
                                                                                                                                                                                                                      :> (Capture
                                                                                                                                                                                                                            "tid"
                                                                                                                                                                                                                            TeamId
                                                                                                                                                                                                                          :> ("features"
                                                                                                                                                                                                                              :> ("limitedEventFanout"
                                                                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (Feature
                                                                                                                                                                                                                                           LimitedEventFanoutConfig)
                                                                                                                                                                                                                                      :> Put
                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                                                                              LimitedEventFanoutConfig)))))))))))))
                                                                                                                                                                                       :<|> Named
                                                                                                                                                                                              '("ipatch",
                                                                                                                                                                                                LimitedEventFanoutConfig)
                                                                                                                                                                                              (Description
                                                                                                                                                                                                 ""
                                                                                                                                                                                               :> (Summary
                                                                                                                                                                                                     "Patch config for limitedEventFanout"
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         OperationDenied
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     TeamFeatureError
                                                                                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                                                                                         '[]
                                                                                                                                                                                                                       :> ("teams"
                                                                                                                                                                                                                           :> (Capture
                                                                                                                                                                                                                                 "tid"
                                                                                                                                                                                                                                 TeamId
                                                                                                                                                                                                                               :> ("features"
                                                                                                                                                                                                                                   :> ("limitedEventFanout"
                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                             (LockableFeaturePatch
                                                                                                                                                                                                                                                LimitedEventFanoutConfig)
                                                                                                                                                                                                                                           :> Patch
                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                                                   LimitedEventFanoutConfig))))))))))))))))))))))))))))))))))
                                                              :<|> (Named
                                                                      '("ilock", FileSharingConfig)
                                                                      (Summary
                                                                         "(Un-)lock fileSharing"
                                                                       :> (Description ""
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("fileSharing"
                                                                                                   :> (Capture
                                                                                                         "lockStatus"
                                                                                                         LockStatus
                                                                                                       :> Put
                                                                                                            '[JSON]
                                                                                                            LockStatusResponse)))))))))
                                                                    :<|> (Named
                                                                            '("ilock",
                                                                              ConferenceCallingConfig)
                                                                            (Summary
                                                                               "(Un-)lock conferenceCalling"
                                                                             :> (Description ""
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("conferenceCalling"
                                                                                                         :> (Capture
                                                                                                               "lockStatus"
                                                                                                               LockStatus
                                                                                                             :> Put
                                                                                                                  '[JSON]
                                                                                                                  LockStatusResponse)))))))))
                                                                          :<|> (Named
                                                                                  '("ilock",
                                                                                    SelfDeletingMessagesConfig)
                                                                                  (Summary
                                                                                     "(Un-)lock selfDeletingMessages"
                                                                                   :> (Description
                                                                                         ""
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("selfDeletingMessages"
                                                                                                               :> (Capture
                                                                                                                     "lockStatus"
                                                                                                                     LockStatus
                                                                                                                   :> Put
                                                                                                                        '[JSON]
                                                                                                                        LockStatusResponse)))))))))
                                                                                :<|> (Named
                                                                                        '("ilock",
                                                                                          GuestLinksConfig)
                                                                                        (Summary
                                                                                           "(Un-)lock conversationGuestLinks"
                                                                                         :> (Description
                                                                                               ""
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'TeamNotFound
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("conversationGuestLinks"
                                                                                                                     :> (Capture
                                                                                                                           "lockStatus"
                                                                                                                           LockStatus
                                                                                                                         :> Put
                                                                                                                              '[JSON]
                                                                                                                              LockStatusResponse)))))))))
                                                                                      :<|> (Named
                                                                                              '("ilock",
                                                                                                SndFactorPasswordChallengeConfig)
                                                                                              (Summary
                                                                                                 "(Un-)lock sndFactorPasswordChallenge"
                                                                                               :> (Description
                                                                                                     ""
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'TeamNotFound
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("sndFactorPasswordChallenge"
                                                                                                                           :> (Capture
                                                                                                                                 "lockStatus"
                                                                                                                                 LockStatus
                                                                                                                               :> Put
                                                                                                                                    '[JSON]
                                                                                                                                    LockStatusResponse)))))))))
                                                                                            :<|> (Named
                                                                                                    '("ilock",
                                                                                                      MLSConfig)
                                                                                                    (Summary
                                                                                                       "(Un-)lock mls"
                                                                                                     :> (Description
                                                                                                           ""
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'TeamNotFound
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("mls"
                                                                                                                                 :> (Capture
                                                                                                                                       "lockStatus"
                                                                                                                                       LockStatus
                                                                                                                                     :> Put
                                                                                                                                          '[JSON]
                                                                                                                                          LockStatusResponse)))))))))
                                                                                                  :<|> (Named
                                                                                                          '("ilock",
                                                                                                            OutlookCalIntegrationConfig)
                                                                                                          (Summary
                                                                                                             "(Un-)lock outlookCalIntegration"
                                                                                                           :> (Description
                                                                                                                 ""
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'TeamNotFound
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("outlookCalIntegration"
                                                                                                                                       :> (Capture
                                                                                                                                             "lockStatus"
                                                                                                                                             LockStatus
                                                                                                                                           :> Put
                                                                                                                                                '[JSON]
                                                                                                                                                LockStatusResponse)))))))))
                                                                                                        :<|> (Named
                                                                                                                '("ilock",
                                                                                                                  MlsE2EIdConfig)
                                                                                                                (Summary
                                                                                                                   "(Un-)lock mlsE2EId"
                                                                                                                 :> (Description
                                                                                                                       ""
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               'TeamNotFound
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("mlsE2EId"
                                                                                                                                             :> (Capture
                                                                                                                                                   "lockStatus"
                                                                                                                                                   LockStatus
                                                                                                                                                 :> Put
                                                                                                                                                      '[JSON]
                                                                                                                                                      LockStatusResponse)))))))))
                                                                                                              :<|> (Named
                                                                                                                      '("ilock",
                                                                                                                        MlsMigrationConfig)
                                                                                                                      (Summary
                                                                                                                         "(Un-)lock mlsMigration"
                                                                                                                       :> (Description
                                                                                                                             ""
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     'TeamNotFound
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("mlsMigration"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "lockStatus"
                                                                                                                                                         LockStatus
                                                                                                                                                       :> Put
                                                                                                                                                            '[JSON]
                                                                                                                                                            LockStatusResponse)))))))))
                                                                                                                    :<|> (Named
                                                                                                                            '("ilock",
                                                                                                                              EnforceFileDownloadLocationConfig)
                                                                                                                            (Summary
                                                                                                                               "(Un-)lock enforceFileDownloadLocation"
                                                                                                                             :> (Description
                                                                                                                                   "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           'TeamNotFound
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("enforceFileDownloadLocation"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "lockStatus"
                                                                                                                                                               LockStatus
                                                                                                                                                             :> Put
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  LockStatusResponse)))))))))
                                                                                                                          :<|> (Named
                                                                                                                                  '("igetmulti",
                                                                                                                                    SearchVisibilityInboundConfig)
                                                                                                                                  (Summary
                                                                                                                                     "Get team feature status in bulk for feature searchVisibilityInbound"
                                                                                                                                   :> ("features-multi-teams"
                                                                                                                                       :> ("searchVisibilityInbound"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 TeamFeatureNoConfigMultiRequest
                                                                                                                                               :> Post
                                                                                                                                                    '[JSON]
                                                                                                                                                    (TeamFeatureNoConfigMultiResponse
                                                                                                                                                       SearchVisibilityInboundConfig)))))
                                                                                                                                :<|> Named
                                                                                                                                       "feature-configs-internal"
                                                                                                                                       (Summary
                                                                                                                                          "Get all feature configs (for user/team; if n/a fall back to site config)."
                                                                                                                                        :> ("feature-configs"
                                                                                                                                            :> (CanThrow
                                                                                                                                                  OperationDenied
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'NotATeamMember
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          'TeamNotFound
                                                                                                                                                        :> (QueryParam'
                                                                                                                                                              '[Optional,
                                                                                                                                                                Strict,
                                                                                                                                                                Description
                                                                                                                                                                  "Optional user id"]
                                                                                                                                                              "user_id"
                                                                                                                                                              UserId
                                                                                                                                                            :> Get
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 AllTeamFeatures))))))))))))))))))
                                                             :<|> (IFederationAPI
                                                                   :<|> (IConversationAPI
                                                                         :<|> IEJPDAPI)))))))))))))
-> OpenApi
forall {k} (api :: k). HasOpenApi api => Proxy api -> OpenApi
toOpenApi (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @InternalAPI)
    OpenApi -> (OpenApi -> OpenApi) -> OpenApi
forall a b. a -> (a -> b) -> b
& (Info -> Identity Info) -> OpenApi -> Identity OpenApi
forall s a. HasInfo s a => Lens' s a
Lens' OpenApi Info
info ((Info -> Identity Info) -> OpenApi -> Identity OpenApi)
-> ((Text -> Identity Text) -> Info -> Identity Info)
-> (Text -> Identity Text)
-> OpenApi
-> Identity OpenApi
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Identity Text) -> Info -> Identity Info
forall s a. HasTitle s a => Lens' s a
Lens' Info Text
title ((Text -> Identity Text) -> OpenApi -> Identity OpenApi)
-> Text -> OpenApi -> OpenApi
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Text
"Wire-Server internal galley API"