{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.Grafana.UpdateWorkspace
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Modifies an existing Amazon Managed Grafana workspace. If you use this
-- operation and omit any optional parameters, the existing values of those
-- parameters are not changed.
--
-- To modify the user authentication methods that the workspace uses, such
-- as SAML or IAM Identity Center, use
-- <https://docs.aws.amazon.com/grafana/latest/APIReference/API_UpdateWorkspaceAuthentication.html UpdateWorkspaceAuthentication>.
--
-- To modify which users in the workspace have the @Admin@ and @Editor@
-- Grafana roles, use
-- <https://docs.aws.amazon.com/grafana/latest/APIReference/API_UpdatePermissions.html UpdatePermissions>.
module Amazonka.Grafana.UpdateWorkspace
  ( -- * Creating a Request
    UpdateWorkspace (..),
    newUpdateWorkspace,

    -- * Request Lenses
    updateWorkspace_accountAccessType,
    updateWorkspace_organizationRoleName,
    updateWorkspace_permissionType,
    updateWorkspace_removeVpcConfiguration,
    updateWorkspace_stackSetName,
    updateWorkspace_vpcConfiguration,
    updateWorkspace_workspaceDataSources,
    updateWorkspace_workspaceDescription,
    updateWorkspace_workspaceName,
    updateWorkspace_workspaceNotificationDestinations,
    updateWorkspace_workspaceOrganizationalUnits,
    updateWorkspace_workspaceRoleArn,
    updateWorkspace_workspaceId,

    -- * Destructuring the Response
    UpdateWorkspaceResponse (..),
    newUpdateWorkspaceResponse,

    -- * Response Lenses
    updateWorkspaceResponse_httpStatus,
    updateWorkspaceResponse_workspace,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Grafana.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateWorkspace' smart constructor.
data UpdateWorkspace = UpdateWorkspace'
  { -- | Specifies whether the workspace can access Amazon Web Services resources
    -- in this Amazon Web Services account only, or whether it can also access
    -- Amazon Web Services resources in other accounts in the same
    -- organization. If you specify @ORGANIZATION@, you must specify which
    -- organizational units the workspace can access in the
    -- @workspaceOrganizationalUnits@ parameter.
    UpdateWorkspace -> Maybe AccountAccessType
accountAccessType :: Prelude.Maybe AccountAccessType,
    -- | The name of an IAM role that already exists to use to access resources
    -- through Organizations.
    UpdateWorkspace -> Maybe (Sensitive Text)
organizationRoleName :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | If you specify @Service Managed@, Amazon Managed Grafana automatically
    -- creates the IAM roles and provisions the permissions that the workspace
    -- needs to use Amazon Web Services data sources and notification channels.
    --
    -- If you specify @CUSTOMER_MANAGED@, you will manage those roles and
    -- permissions yourself. If you are creating this workspace in a member
    -- account of an organization and that account is not a delegated
    -- administrator account, and you want the workspace to access data sources
    -- in other Amazon Web Services accounts in the organization, you must
    -- choose @CUSTOMER_MANAGED@.
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/grafana/latest/userguide/AMG-manage-permissions.html Amazon Managed Grafana permissions and policies for Amazon Web Services data sources and notification channels>
    UpdateWorkspace -> Maybe PermissionType
permissionType :: Prelude.Maybe PermissionType,
    -- | Whether to remove the VPC configuration from the workspace.
    --
    -- Setting this to @true@ and providing a @vpcConfiguration@ to set will
    -- return an error.
    UpdateWorkspace -> Maybe Bool
removeVpcConfiguration :: Prelude.Maybe Prelude.Bool,
    -- | The name of the CloudFormation stack set to use to generate IAM roles to
    -- be used for this workspace.
    UpdateWorkspace -> Maybe Text
stackSetName :: Prelude.Maybe Prelude.Text,
    -- | The configuration settings for an Amazon VPC that contains data sources
    -- for your Grafana workspace to connect to.
    UpdateWorkspace -> Maybe VpcConfiguration
vpcConfiguration :: Prelude.Maybe VpcConfiguration,
    -- | Specify the Amazon Web Services data sources that you want to be queried
    -- in this workspace. Specifying these data sources here enables Amazon
    -- Managed Grafana to create IAM roles and permissions that allow Amazon
    -- Managed Grafana to read data from these sources. You must still add them
    -- as data sources in the Grafana console in the workspace.
    --
    -- If you don\'t specify a data source here, you can still add it as a data
    -- source later in the workspace console. However, you will then have to
    -- manually configure permissions for it.
    UpdateWorkspace -> Maybe [DataSourceType]
workspaceDataSources :: Prelude.Maybe [DataSourceType],
    -- | A description for the workspace. This is used only to help you identify
    -- this workspace.
    UpdateWorkspace -> Maybe (Sensitive Text)
workspaceDescription :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | A new name for the workspace to update.
    UpdateWorkspace -> Maybe (Sensitive Text)
workspaceName :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | Specify the Amazon Web Services notification channels that you plan to
    -- use in this workspace. Specifying these data sources here enables Amazon
    -- Managed Grafana to create IAM roles and permissions that allow Amazon
    -- Managed Grafana to use these channels.
    UpdateWorkspace -> Maybe [NotificationDestinationType]
workspaceNotificationDestinations :: Prelude.Maybe [NotificationDestinationType],
    -- | Specifies the organizational units that this workspace is allowed to use
    -- data sources from, if this workspace is in an account that is part of an
    -- organization.
    UpdateWorkspace -> Maybe (Sensitive [Text])
workspaceOrganizationalUnits :: Prelude.Maybe (Data.Sensitive [Prelude.Text]),
    -- | The workspace needs an IAM role that grants permissions to the Amazon
    -- Web Services resources that the workspace will view data from. If you
    -- already have a role that you want to use, specify it here. If you omit
    -- this field and you specify some Amazon Web Services resources in
    -- @workspaceDataSources@ or @workspaceNotificationDestinations@, a new IAM
    -- role with the necessary permissions is automatically created.
    UpdateWorkspace -> Maybe (Sensitive Text)
workspaceRoleArn :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The ID of the workspace to update.
    UpdateWorkspace -> Text
workspaceId :: Prelude.Text
  }
  deriving (UpdateWorkspace -> UpdateWorkspace -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateWorkspace -> UpdateWorkspace -> Bool
$c/= :: UpdateWorkspace -> UpdateWorkspace -> Bool
== :: UpdateWorkspace -> UpdateWorkspace -> Bool
$c== :: UpdateWorkspace -> UpdateWorkspace -> Bool
Prelude.Eq, Int -> UpdateWorkspace -> ShowS
[UpdateWorkspace] -> ShowS
UpdateWorkspace -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateWorkspace] -> ShowS
$cshowList :: [UpdateWorkspace] -> ShowS
show :: UpdateWorkspace -> String
$cshow :: UpdateWorkspace -> String
showsPrec :: Int -> UpdateWorkspace -> ShowS
$cshowsPrec :: Int -> UpdateWorkspace -> ShowS
Prelude.Show, forall x. Rep UpdateWorkspace x -> UpdateWorkspace
forall x. UpdateWorkspace -> Rep UpdateWorkspace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateWorkspace x -> UpdateWorkspace
$cfrom :: forall x. UpdateWorkspace -> Rep UpdateWorkspace x
Prelude.Generic)

-- |
-- Create a value of 'UpdateWorkspace' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'accountAccessType', 'updateWorkspace_accountAccessType' - Specifies whether the workspace can access Amazon Web Services resources
-- in this Amazon Web Services account only, or whether it can also access
-- Amazon Web Services resources in other accounts in the same
-- organization. If you specify @ORGANIZATION@, you must specify which
-- organizational units the workspace can access in the
-- @workspaceOrganizationalUnits@ parameter.
--
-- 'organizationRoleName', 'updateWorkspace_organizationRoleName' - The name of an IAM role that already exists to use to access resources
-- through Organizations.
--
-- 'permissionType', 'updateWorkspace_permissionType' - If you specify @Service Managed@, Amazon Managed Grafana automatically
-- creates the IAM roles and provisions the permissions that the workspace
-- needs to use Amazon Web Services data sources and notification channels.
--
-- If you specify @CUSTOMER_MANAGED@, you will manage those roles and
-- permissions yourself. If you are creating this workspace in a member
-- account of an organization and that account is not a delegated
-- administrator account, and you want the workspace to access data sources
-- in other Amazon Web Services accounts in the organization, you must
-- choose @CUSTOMER_MANAGED@.
--
-- For more information, see
-- <https://docs.aws.amazon.com/grafana/latest/userguide/AMG-manage-permissions.html Amazon Managed Grafana permissions and policies for Amazon Web Services data sources and notification channels>
--
-- 'removeVpcConfiguration', 'updateWorkspace_removeVpcConfiguration' - Whether to remove the VPC configuration from the workspace.
--
-- Setting this to @true@ and providing a @vpcConfiguration@ to set will
-- return an error.
--
-- 'stackSetName', 'updateWorkspace_stackSetName' - The name of the CloudFormation stack set to use to generate IAM roles to
-- be used for this workspace.
--
-- 'vpcConfiguration', 'updateWorkspace_vpcConfiguration' - The configuration settings for an Amazon VPC that contains data sources
-- for your Grafana workspace to connect to.
--
-- 'workspaceDataSources', 'updateWorkspace_workspaceDataSources' - Specify the Amazon Web Services data sources that you want to be queried
-- in this workspace. Specifying these data sources here enables Amazon
-- Managed Grafana to create IAM roles and permissions that allow Amazon
-- Managed Grafana to read data from these sources. You must still add them
-- as data sources in the Grafana console in the workspace.
--
-- If you don\'t specify a data source here, you can still add it as a data
-- source later in the workspace console. However, you will then have to
-- manually configure permissions for it.
--
-- 'workspaceDescription', 'updateWorkspace_workspaceDescription' - A description for the workspace. This is used only to help you identify
-- this workspace.
--
-- 'workspaceName', 'updateWorkspace_workspaceName' - A new name for the workspace to update.
--
-- 'workspaceNotificationDestinations', 'updateWorkspace_workspaceNotificationDestinations' - Specify the Amazon Web Services notification channels that you plan to
-- use in this workspace. Specifying these data sources here enables Amazon
-- Managed Grafana to create IAM roles and permissions that allow Amazon
-- Managed Grafana to use these channels.
--
-- 'workspaceOrganizationalUnits', 'updateWorkspace_workspaceOrganizationalUnits' - Specifies the organizational units that this workspace is allowed to use
-- data sources from, if this workspace is in an account that is part of an
-- organization.
--
-- 'workspaceRoleArn', 'updateWorkspace_workspaceRoleArn' - The workspace needs an IAM role that grants permissions to the Amazon
-- Web Services resources that the workspace will view data from. If you
-- already have a role that you want to use, specify it here. If you omit
-- this field and you specify some Amazon Web Services resources in
-- @workspaceDataSources@ or @workspaceNotificationDestinations@, a new IAM
-- role with the necessary permissions is automatically created.
--
-- 'workspaceId', 'updateWorkspace_workspaceId' - The ID of the workspace to update.
newUpdateWorkspace ::
  -- | 'workspaceId'
  Prelude.Text ->
  UpdateWorkspace
newUpdateWorkspace :: Text -> UpdateWorkspace
newUpdateWorkspace Text
pWorkspaceId_ =
  UpdateWorkspace'
    { $sel:accountAccessType:UpdateWorkspace' :: Maybe AccountAccessType
accountAccessType =
        forall a. Maybe a
Prelude.Nothing,
      $sel:organizationRoleName:UpdateWorkspace' :: Maybe (Sensitive Text)
organizationRoleName = forall a. Maybe a
Prelude.Nothing,
      $sel:permissionType:UpdateWorkspace' :: Maybe PermissionType
permissionType = forall a. Maybe a
Prelude.Nothing,
      $sel:removeVpcConfiguration:UpdateWorkspace' :: Maybe Bool
removeVpcConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:stackSetName:UpdateWorkspace' :: Maybe Text
stackSetName = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcConfiguration:UpdateWorkspace' :: Maybe VpcConfiguration
vpcConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:workspaceDataSources:UpdateWorkspace' :: Maybe [DataSourceType]
workspaceDataSources = forall a. Maybe a
Prelude.Nothing,
      $sel:workspaceDescription:UpdateWorkspace' :: Maybe (Sensitive Text)
workspaceDescription = forall a. Maybe a
Prelude.Nothing,
      $sel:workspaceName:UpdateWorkspace' :: Maybe (Sensitive Text)
workspaceName = forall a. Maybe a
Prelude.Nothing,
      $sel:workspaceNotificationDestinations:UpdateWorkspace' :: Maybe [NotificationDestinationType]
workspaceNotificationDestinations = forall a. Maybe a
Prelude.Nothing,
      $sel:workspaceOrganizationalUnits:UpdateWorkspace' :: Maybe (Sensitive [Text])
workspaceOrganizationalUnits = forall a. Maybe a
Prelude.Nothing,
      $sel:workspaceRoleArn:UpdateWorkspace' :: Maybe (Sensitive Text)
workspaceRoleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:workspaceId:UpdateWorkspace' :: Text
workspaceId = Text
pWorkspaceId_
    }

-- | Specifies whether the workspace can access Amazon Web Services resources
-- in this Amazon Web Services account only, or whether it can also access
-- Amazon Web Services resources in other accounts in the same
-- organization. If you specify @ORGANIZATION@, you must specify which
-- organizational units the workspace can access in the
-- @workspaceOrganizationalUnits@ parameter.
updateWorkspace_accountAccessType :: Lens.Lens' UpdateWorkspace (Prelude.Maybe AccountAccessType)
updateWorkspace_accountAccessType :: Lens' UpdateWorkspace (Maybe AccountAccessType)
updateWorkspace_accountAccessType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspace' {Maybe AccountAccessType
accountAccessType :: Maybe AccountAccessType
$sel:accountAccessType:UpdateWorkspace' :: UpdateWorkspace -> Maybe AccountAccessType
accountAccessType} -> Maybe AccountAccessType
accountAccessType) (\s :: UpdateWorkspace
s@UpdateWorkspace' {} Maybe AccountAccessType
a -> UpdateWorkspace
s {$sel:accountAccessType:UpdateWorkspace' :: Maybe AccountAccessType
accountAccessType = Maybe AccountAccessType
a} :: UpdateWorkspace)

-- | The name of an IAM role that already exists to use to access resources
-- through Organizations.
updateWorkspace_organizationRoleName :: Lens.Lens' UpdateWorkspace (Prelude.Maybe Prelude.Text)
updateWorkspace_organizationRoleName :: Lens' UpdateWorkspace (Maybe Text)
updateWorkspace_organizationRoleName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspace' {Maybe (Sensitive Text)
organizationRoleName :: Maybe (Sensitive Text)
$sel:organizationRoleName:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive Text)
organizationRoleName} -> Maybe (Sensitive Text)
organizationRoleName) (\s :: UpdateWorkspace
s@UpdateWorkspace' {} Maybe (Sensitive Text)
a -> UpdateWorkspace
s {$sel:organizationRoleName:UpdateWorkspace' :: Maybe (Sensitive Text)
organizationRoleName = Maybe (Sensitive Text)
a} :: UpdateWorkspace) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | If you specify @Service Managed@, Amazon Managed Grafana automatically
-- creates the IAM roles and provisions the permissions that the workspace
-- needs to use Amazon Web Services data sources and notification channels.
--
-- If you specify @CUSTOMER_MANAGED@, you will manage those roles and
-- permissions yourself. If you are creating this workspace in a member
-- account of an organization and that account is not a delegated
-- administrator account, and you want the workspace to access data sources
-- in other Amazon Web Services accounts in the organization, you must
-- choose @CUSTOMER_MANAGED@.
--
-- For more information, see
-- <https://docs.aws.amazon.com/grafana/latest/userguide/AMG-manage-permissions.html Amazon Managed Grafana permissions and policies for Amazon Web Services data sources and notification channels>
updateWorkspace_permissionType :: Lens.Lens' UpdateWorkspace (Prelude.Maybe PermissionType)
updateWorkspace_permissionType :: Lens' UpdateWorkspace (Maybe PermissionType)
updateWorkspace_permissionType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspace' {Maybe PermissionType
permissionType :: Maybe PermissionType
$sel:permissionType:UpdateWorkspace' :: UpdateWorkspace -> Maybe PermissionType
permissionType} -> Maybe PermissionType
permissionType) (\s :: UpdateWorkspace
s@UpdateWorkspace' {} Maybe PermissionType
a -> UpdateWorkspace
s {$sel:permissionType:UpdateWorkspace' :: Maybe PermissionType
permissionType = Maybe PermissionType
a} :: UpdateWorkspace)

-- | Whether to remove the VPC configuration from the workspace.
--
-- Setting this to @true@ and providing a @vpcConfiguration@ to set will
-- return an error.
updateWorkspace_removeVpcConfiguration :: Lens.Lens' UpdateWorkspace (Prelude.Maybe Prelude.Bool)
updateWorkspace_removeVpcConfiguration :: Lens' UpdateWorkspace (Maybe Bool)
updateWorkspace_removeVpcConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspace' {Maybe Bool
removeVpcConfiguration :: Maybe Bool
$sel:removeVpcConfiguration:UpdateWorkspace' :: UpdateWorkspace -> Maybe Bool
removeVpcConfiguration} -> Maybe Bool
removeVpcConfiguration) (\s :: UpdateWorkspace
s@UpdateWorkspace' {} Maybe Bool
a -> UpdateWorkspace
s {$sel:removeVpcConfiguration:UpdateWorkspace' :: Maybe Bool
removeVpcConfiguration = Maybe Bool
a} :: UpdateWorkspace)

-- | The name of the CloudFormation stack set to use to generate IAM roles to
-- be used for this workspace.
updateWorkspace_stackSetName :: Lens.Lens' UpdateWorkspace (Prelude.Maybe Prelude.Text)
updateWorkspace_stackSetName :: Lens' UpdateWorkspace (Maybe Text)
updateWorkspace_stackSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspace' {Maybe Text
stackSetName :: Maybe Text
$sel:stackSetName:UpdateWorkspace' :: UpdateWorkspace -> Maybe Text
stackSetName} -> Maybe Text
stackSetName) (\s :: UpdateWorkspace
s@UpdateWorkspace' {} Maybe Text
a -> UpdateWorkspace
s {$sel:stackSetName:UpdateWorkspace' :: Maybe Text
stackSetName = Maybe Text
a} :: UpdateWorkspace)

-- | The configuration settings for an Amazon VPC that contains data sources
-- for your Grafana workspace to connect to.
updateWorkspace_vpcConfiguration :: Lens.Lens' UpdateWorkspace (Prelude.Maybe VpcConfiguration)
updateWorkspace_vpcConfiguration :: Lens' UpdateWorkspace (Maybe VpcConfiguration)
updateWorkspace_vpcConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspace' {Maybe VpcConfiguration
vpcConfiguration :: Maybe VpcConfiguration
$sel:vpcConfiguration:UpdateWorkspace' :: UpdateWorkspace -> Maybe VpcConfiguration
vpcConfiguration} -> Maybe VpcConfiguration
vpcConfiguration) (\s :: UpdateWorkspace
s@UpdateWorkspace' {} Maybe VpcConfiguration
a -> UpdateWorkspace
s {$sel:vpcConfiguration:UpdateWorkspace' :: Maybe VpcConfiguration
vpcConfiguration = Maybe VpcConfiguration
a} :: UpdateWorkspace)

-- | Specify the Amazon Web Services data sources that you want to be queried
-- in this workspace. Specifying these data sources here enables Amazon
-- Managed Grafana to create IAM roles and permissions that allow Amazon
-- Managed Grafana to read data from these sources. You must still add them
-- as data sources in the Grafana console in the workspace.
--
-- If you don\'t specify a data source here, you can still add it as a data
-- source later in the workspace console. However, you will then have to
-- manually configure permissions for it.
updateWorkspace_workspaceDataSources :: Lens.Lens' UpdateWorkspace (Prelude.Maybe [DataSourceType])
updateWorkspace_workspaceDataSources :: Lens' UpdateWorkspace (Maybe [DataSourceType])
updateWorkspace_workspaceDataSources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspace' {Maybe [DataSourceType]
workspaceDataSources :: Maybe [DataSourceType]
$sel:workspaceDataSources:UpdateWorkspace' :: UpdateWorkspace -> Maybe [DataSourceType]
workspaceDataSources} -> Maybe [DataSourceType]
workspaceDataSources) (\s :: UpdateWorkspace
s@UpdateWorkspace' {} Maybe [DataSourceType]
a -> UpdateWorkspace
s {$sel:workspaceDataSources:UpdateWorkspace' :: Maybe [DataSourceType]
workspaceDataSources = Maybe [DataSourceType]
a} :: UpdateWorkspace) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | A description for the workspace. This is used only to help you identify
-- this workspace.
updateWorkspace_workspaceDescription :: Lens.Lens' UpdateWorkspace (Prelude.Maybe Prelude.Text)
updateWorkspace_workspaceDescription :: Lens' UpdateWorkspace (Maybe Text)
updateWorkspace_workspaceDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspace' {Maybe (Sensitive Text)
workspaceDescription :: Maybe (Sensitive Text)
$sel:workspaceDescription:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive Text)
workspaceDescription} -> Maybe (Sensitive Text)
workspaceDescription) (\s :: UpdateWorkspace
s@UpdateWorkspace' {} Maybe (Sensitive Text)
a -> UpdateWorkspace
s {$sel:workspaceDescription:UpdateWorkspace' :: Maybe (Sensitive Text)
workspaceDescription = Maybe (Sensitive Text)
a} :: UpdateWorkspace) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | A new name for the workspace to update.
updateWorkspace_workspaceName :: Lens.Lens' UpdateWorkspace (Prelude.Maybe Prelude.Text)
updateWorkspace_workspaceName :: Lens' UpdateWorkspace (Maybe Text)
updateWorkspace_workspaceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspace' {Maybe (Sensitive Text)
workspaceName :: Maybe (Sensitive Text)
$sel:workspaceName:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive Text)
workspaceName} -> Maybe (Sensitive Text)
workspaceName) (\s :: UpdateWorkspace
s@UpdateWorkspace' {} Maybe (Sensitive Text)
a -> UpdateWorkspace
s {$sel:workspaceName:UpdateWorkspace' :: Maybe (Sensitive Text)
workspaceName = Maybe (Sensitive Text)
a} :: UpdateWorkspace) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | Specify the Amazon Web Services notification channels that you plan to
-- use in this workspace. Specifying these data sources here enables Amazon
-- Managed Grafana to create IAM roles and permissions that allow Amazon
-- Managed Grafana to use these channels.
updateWorkspace_workspaceNotificationDestinations :: Lens.Lens' UpdateWorkspace (Prelude.Maybe [NotificationDestinationType])
updateWorkspace_workspaceNotificationDestinations :: Lens' UpdateWorkspace (Maybe [NotificationDestinationType])
updateWorkspace_workspaceNotificationDestinations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspace' {Maybe [NotificationDestinationType]
workspaceNotificationDestinations :: Maybe [NotificationDestinationType]
$sel:workspaceNotificationDestinations:UpdateWorkspace' :: UpdateWorkspace -> Maybe [NotificationDestinationType]
workspaceNotificationDestinations} -> Maybe [NotificationDestinationType]
workspaceNotificationDestinations) (\s :: UpdateWorkspace
s@UpdateWorkspace' {} Maybe [NotificationDestinationType]
a -> UpdateWorkspace
s {$sel:workspaceNotificationDestinations:UpdateWorkspace' :: Maybe [NotificationDestinationType]
workspaceNotificationDestinations = Maybe [NotificationDestinationType]
a} :: UpdateWorkspace) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | Specifies the organizational units that this workspace is allowed to use
-- data sources from, if this workspace is in an account that is part of an
-- organization.
updateWorkspace_workspaceOrganizationalUnits :: Lens.Lens' UpdateWorkspace (Prelude.Maybe [Prelude.Text])
updateWorkspace_workspaceOrganizationalUnits :: Lens' UpdateWorkspace (Maybe [Text])
updateWorkspace_workspaceOrganizationalUnits = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspace' {Maybe (Sensitive [Text])
workspaceOrganizationalUnits :: Maybe (Sensitive [Text])
$sel:workspaceOrganizationalUnits:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive [Text])
workspaceOrganizationalUnits} -> Maybe (Sensitive [Text])
workspaceOrganizationalUnits) (\s :: UpdateWorkspace
s@UpdateWorkspace' {} Maybe (Sensitive [Text])
a -> UpdateWorkspace
s {$sel:workspaceOrganizationalUnits:UpdateWorkspace' :: Maybe (Sensitive [Text])
workspaceOrganizationalUnits = Maybe (Sensitive [Text])
a} :: UpdateWorkspace) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping (forall a. Iso' (Sensitive a) a
Data._Sensitive forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced)

-- | The workspace needs an IAM role that grants permissions to the Amazon
-- Web Services resources that the workspace will view data from. If you
-- already have a role that you want to use, specify it here. If you omit
-- this field and you specify some Amazon Web Services resources in
-- @workspaceDataSources@ or @workspaceNotificationDestinations@, a new IAM
-- role with the necessary permissions is automatically created.
updateWorkspace_workspaceRoleArn :: Lens.Lens' UpdateWorkspace (Prelude.Maybe Prelude.Text)
updateWorkspace_workspaceRoleArn :: Lens' UpdateWorkspace (Maybe Text)
updateWorkspace_workspaceRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspace' {Maybe (Sensitive Text)
workspaceRoleArn :: Maybe (Sensitive Text)
$sel:workspaceRoleArn:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive Text)
workspaceRoleArn} -> Maybe (Sensitive Text)
workspaceRoleArn) (\s :: UpdateWorkspace
s@UpdateWorkspace' {} Maybe (Sensitive Text)
a -> UpdateWorkspace
s {$sel:workspaceRoleArn:UpdateWorkspace' :: Maybe (Sensitive Text)
workspaceRoleArn = Maybe (Sensitive Text)
a} :: UpdateWorkspace) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | The ID of the workspace to update.
updateWorkspace_workspaceId :: Lens.Lens' UpdateWorkspace Prelude.Text
updateWorkspace_workspaceId :: Lens' UpdateWorkspace Text
updateWorkspace_workspaceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspace' {Text
workspaceId :: Text
$sel:workspaceId:UpdateWorkspace' :: UpdateWorkspace -> Text
workspaceId} -> Text
workspaceId) (\s :: UpdateWorkspace
s@UpdateWorkspace' {} Text
a -> UpdateWorkspace
s {$sel:workspaceId:UpdateWorkspace' :: Text
workspaceId = Text
a} :: UpdateWorkspace)

instance Core.AWSRequest UpdateWorkspace where
  type
    AWSResponse UpdateWorkspace =
      UpdateWorkspaceResponse
  request :: (Service -> Service) -> UpdateWorkspace -> Request UpdateWorkspace
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateWorkspace
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateWorkspace)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Int -> WorkspaceDescription -> UpdateWorkspaceResponse
UpdateWorkspaceResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"workspace")
      )

instance Prelude.Hashable UpdateWorkspace where
  hashWithSalt :: Int -> UpdateWorkspace -> Int
hashWithSalt Int
_salt UpdateWorkspace' {Maybe Bool
Maybe [DataSourceType]
Maybe [NotificationDestinationType]
Maybe Text
Maybe (Sensitive [Text])
Maybe (Sensitive Text)
Maybe AccountAccessType
Maybe PermissionType
Maybe VpcConfiguration
Text
workspaceId :: Text
workspaceRoleArn :: Maybe (Sensitive Text)
workspaceOrganizationalUnits :: Maybe (Sensitive [Text])
workspaceNotificationDestinations :: Maybe [NotificationDestinationType]
workspaceName :: Maybe (Sensitive Text)
workspaceDescription :: Maybe (Sensitive Text)
workspaceDataSources :: Maybe [DataSourceType]
vpcConfiguration :: Maybe VpcConfiguration
stackSetName :: Maybe Text
removeVpcConfiguration :: Maybe Bool
permissionType :: Maybe PermissionType
organizationRoleName :: Maybe (Sensitive Text)
accountAccessType :: Maybe AccountAccessType
$sel:workspaceId:UpdateWorkspace' :: UpdateWorkspace -> Text
$sel:workspaceRoleArn:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive Text)
$sel:workspaceOrganizationalUnits:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive [Text])
$sel:workspaceNotificationDestinations:UpdateWorkspace' :: UpdateWorkspace -> Maybe [NotificationDestinationType]
$sel:workspaceName:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive Text)
$sel:workspaceDescription:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive Text)
$sel:workspaceDataSources:UpdateWorkspace' :: UpdateWorkspace -> Maybe [DataSourceType]
$sel:vpcConfiguration:UpdateWorkspace' :: UpdateWorkspace -> Maybe VpcConfiguration
$sel:stackSetName:UpdateWorkspace' :: UpdateWorkspace -> Maybe Text
$sel:removeVpcConfiguration:UpdateWorkspace' :: UpdateWorkspace -> Maybe Bool
$sel:permissionType:UpdateWorkspace' :: UpdateWorkspace -> Maybe PermissionType
$sel:organizationRoleName:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive Text)
$sel:accountAccessType:UpdateWorkspace' :: UpdateWorkspace -> Maybe AccountAccessType
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AccountAccessType
accountAccessType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
organizationRoleName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PermissionType
permissionType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
removeVpcConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
stackSetName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VpcConfiguration
vpcConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [DataSourceType]
workspaceDataSources
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
workspaceDescription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
workspaceName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [NotificationDestinationType]
workspaceNotificationDestinations
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive [Text])
workspaceOrganizationalUnits
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
workspaceRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
workspaceId

instance Prelude.NFData UpdateWorkspace where
  rnf :: UpdateWorkspace -> ()
rnf UpdateWorkspace' {Maybe Bool
Maybe [DataSourceType]
Maybe [NotificationDestinationType]
Maybe Text
Maybe (Sensitive [Text])
Maybe (Sensitive Text)
Maybe AccountAccessType
Maybe PermissionType
Maybe VpcConfiguration
Text
workspaceId :: Text
workspaceRoleArn :: Maybe (Sensitive Text)
workspaceOrganizationalUnits :: Maybe (Sensitive [Text])
workspaceNotificationDestinations :: Maybe [NotificationDestinationType]
workspaceName :: Maybe (Sensitive Text)
workspaceDescription :: Maybe (Sensitive Text)
workspaceDataSources :: Maybe [DataSourceType]
vpcConfiguration :: Maybe VpcConfiguration
stackSetName :: Maybe Text
removeVpcConfiguration :: Maybe Bool
permissionType :: Maybe PermissionType
organizationRoleName :: Maybe (Sensitive Text)
accountAccessType :: Maybe AccountAccessType
$sel:workspaceId:UpdateWorkspace' :: UpdateWorkspace -> Text
$sel:workspaceRoleArn:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive Text)
$sel:workspaceOrganizationalUnits:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive [Text])
$sel:workspaceNotificationDestinations:UpdateWorkspace' :: UpdateWorkspace -> Maybe [NotificationDestinationType]
$sel:workspaceName:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive Text)
$sel:workspaceDescription:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive Text)
$sel:workspaceDataSources:UpdateWorkspace' :: UpdateWorkspace -> Maybe [DataSourceType]
$sel:vpcConfiguration:UpdateWorkspace' :: UpdateWorkspace -> Maybe VpcConfiguration
$sel:stackSetName:UpdateWorkspace' :: UpdateWorkspace -> Maybe Text
$sel:removeVpcConfiguration:UpdateWorkspace' :: UpdateWorkspace -> Maybe Bool
$sel:permissionType:UpdateWorkspace' :: UpdateWorkspace -> Maybe PermissionType
$sel:organizationRoleName:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive Text)
$sel:accountAccessType:UpdateWorkspace' :: UpdateWorkspace -> Maybe AccountAccessType
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AccountAccessType
accountAccessType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
organizationRoleName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PermissionType
permissionType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
removeVpcConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
stackSetName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe VpcConfiguration
vpcConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [DataSourceType]
workspaceDataSources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
workspaceDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
workspaceName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [NotificationDestinationType]
workspaceNotificationDestinations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive [Text])
workspaceOrganizationalUnits
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
workspaceRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
workspaceId

instance Data.ToHeaders UpdateWorkspace where
  toHeaders :: UpdateWorkspace -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateWorkspace where
  toJSON :: UpdateWorkspace -> Value
toJSON UpdateWorkspace' {Maybe Bool
Maybe [DataSourceType]
Maybe [NotificationDestinationType]
Maybe Text
Maybe (Sensitive [Text])
Maybe (Sensitive Text)
Maybe AccountAccessType
Maybe PermissionType
Maybe VpcConfiguration
Text
workspaceId :: Text
workspaceRoleArn :: Maybe (Sensitive Text)
workspaceOrganizationalUnits :: Maybe (Sensitive [Text])
workspaceNotificationDestinations :: Maybe [NotificationDestinationType]
workspaceName :: Maybe (Sensitive Text)
workspaceDescription :: Maybe (Sensitive Text)
workspaceDataSources :: Maybe [DataSourceType]
vpcConfiguration :: Maybe VpcConfiguration
stackSetName :: Maybe Text
removeVpcConfiguration :: Maybe Bool
permissionType :: Maybe PermissionType
organizationRoleName :: Maybe (Sensitive Text)
accountAccessType :: Maybe AccountAccessType
$sel:workspaceId:UpdateWorkspace' :: UpdateWorkspace -> Text
$sel:workspaceRoleArn:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive Text)
$sel:workspaceOrganizationalUnits:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive [Text])
$sel:workspaceNotificationDestinations:UpdateWorkspace' :: UpdateWorkspace -> Maybe [NotificationDestinationType]
$sel:workspaceName:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive Text)
$sel:workspaceDescription:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive Text)
$sel:workspaceDataSources:UpdateWorkspace' :: UpdateWorkspace -> Maybe [DataSourceType]
$sel:vpcConfiguration:UpdateWorkspace' :: UpdateWorkspace -> Maybe VpcConfiguration
$sel:stackSetName:UpdateWorkspace' :: UpdateWorkspace -> Maybe Text
$sel:removeVpcConfiguration:UpdateWorkspace' :: UpdateWorkspace -> Maybe Bool
$sel:permissionType:UpdateWorkspace' :: UpdateWorkspace -> Maybe PermissionType
$sel:organizationRoleName:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive Text)
$sel:accountAccessType:UpdateWorkspace' :: UpdateWorkspace -> Maybe AccountAccessType
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"accountAccessType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AccountAccessType
accountAccessType,
            (Key
"organizationRoleName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Sensitive Text)
organizationRoleName,
            (Key
"permissionType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe PermissionType
permissionType,
            (Key
"removeVpcConfiguration" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
removeVpcConfiguration,
            (Key
"stackSetName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
stackSetName,
            (Key
"vpcConfiguration" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe VpcConfiguration
vpcConfiguration,
            (Key
"workspaceDataSources" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [DataSourceType]
workspaceDataSources,
            (Key
"workspaceDescription" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Sensitive Text)
workspaceDescription,
            (Key
"workspaceName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Sensitive Text)
workspaceName,
            (Key
"workspaceNotificationDestinations" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [NotificationDestinationType]
workspaceNotificationDestinations,
            (Key
"workspaceOrganizationalUnits" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Sensitive [Text])
workspaceOrganizationalUnits,
            (Key
"workspaceRoleArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Sensitive Text)
workspaceRoleArn
          ]
      )

instance Data.ToPath UpdateWorkspace where
  toPath :: UpdateWorkspace -> ByteString
toPath UpdateWorkspace' {Maybe Bool
Maybe [DataSourceType]
Maybe [NotificationDestinationType]
Maybe Text
Maybe (Sensitive [Text])
Maybe (Sensitive Text)
Maybe AccountAccessType
Maybe PermissionType
Maybe VpcConfiguration
Text
workspaceId :: Text
workspaceRoleArn :: Maybe (Sensitive Text)
workspaceOrganizationalUnits :: Maybe (Sensitive [Text])
workspaceNotificationDestinations :: Maybe [NotificationDestinationType]
workspaceName :: Maybe (Sensitive Text)
workspaceDescription :: Maybe (Sensitive Text)
workspaceDataSources :: Maybe [DataSourceType]
vpcConfiguration :: Maybe VpcConfiguration
stackSetName :: Maybe Text
removeVpcConfiguration :: Maybe Bool
permissionType :: Maybe PermissionType
organizationRoleName :: Maybe (Sensitive Text)
accountAccessType :: Maybe AccountAccessType
$sel:workspaceId:UpdateWorkspace' :: UpdateWorkspace -> Text
$sel:workspaceRoleArn:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive Text)
$sel:workspaceOrganizationalUnits:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive [Text])
$sel:workspaceNotificationDestinations:UpdateWorkspace' :: UpdateWorkspace -> Maybe [NotificationDestinationType]
$sel:workspaceName:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive Text)
$sel:workspaceDescription:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive Text)
$sel:workspaceDataSources:UpdateWorkspace' :: UpdateWorkspace -> Maybe [DataSourceType]
$sel:vpcConfiguration:UpdateWorkspace' :: UpdateWorkspace -> Maybe VpcConfiguration
$sel:stackSetName:UpdateWorkspace' :: UpdateWorkspace -> Maybe Text
$sel:removeVpcConfiguration:UpdateWorkspace' :: UpdateWorkspace -> Maybe Bool
$sel:permissionType:UpdateWorkspace' :: UpdateWorkspace -> Maybe PermissionType
$sel:organizationRoleName:UpdateWorkspace' :: UpdateWorkspace -> Maybe (Sensitive Text)
$sel:accountAccessType:UpdateWorkspace' :: UpdateWorkspace -> Maybe AccountAccessType
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/workspaces/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
workspaceId]

instance Data.ToQuery UpdateWorkspace where
  toQuery :: UpdateWorkspace -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newUpdateWorkspaceResponse' smart constructor.
data UpdateWorkspaceResponse = UpdateWorkspaceResponse'
  { -- | The response's http status code.
    UpdateWorkspaceResponse -> Int
httpStatus :: Prelude.Int,
    -- | A structure containing data about the workspace that was created.
    UpdateWorkspaceResponse -> WorkspaceDescription
workspace :: WorkspaceDescription
  }
  deriving (UpdateWorkspaceResponse -> UpdateWorkspaceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateWorkspaceResponse -> UpdateWorkspaceResponse -> Bool
$c/= :: UpdateWorkspaceResponse -> UpdateWorkspaceResponse -> Bool
== :: UpdateWorkspaceResponse -> UpdateWorkspaceResponse -> Bool
$c== :: UpdateWorkspaceResponse -> UpdateWorkspaceResponse -> Bool
Prelude.Eq, Int -> UpdateWorkspaceResponse -> ShowS
[UpdateWorkspaceResponse] -> ShowS
UpdateWorkspaceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateWorkspaceResponse] -> ShowS
$cshowList :: [UpdateWorkspaceResponse] -> ShowS
show :: UpdateWorkspaceResponse -> String
$cshow :: UpdateWorkspaceResponse -> String
showsPrec :: Int -> UpdateWorkspaceResponse -> ShowS
$cshowsPrec :: Int -> UpdateWorkspaceResponse -> ShowS
Prelude.Show, forall x. Rep UpdateWorkspaceResponse x -> UpdateWorkspaceResponse
forall x. UpdateWorkspaceResponse -> Rep UpdateWorkspaceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateWorkspaceResponse x -> UpdateWorkspaceResponse
$cfrom :: forall x. UpdateWorkspaceResponse -> Rep UpdateWorkspaceResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateWorkspaceResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'httpStatus', 'updateWorkspaceResponse_httpStatus' - The response's http status code.
--
-- 'workspace', 'updateWorkspaceResponse_workspace' - A structure containing data about the workspace that was created.
newUpdateWorkspaceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'workspace'
  WorkspaceDescription ->
  UpdateWorkspaceResponse
newUpdateWorkspaceResponse :: Int -> WorkspaceDescription -> UpdateWorkspaceResponse
newUpdateWorkspaceResponse Int
pHttpStatus_ WorkspaceDescription
pWorkspace_ =
  UpdateWorkspaceResponse'
    { $sel:httpStatus:UpdateWorkspaceResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:workspace:UpdateWorkspaceResponse' :: WorkspaceDescription
workspace = WorkspaceDescription
pWorkspace_
    }

-- | The response's http status code.
updateWorkspaceResponse_httpStatus :: Lens.Lens' UpdateWorkspaceResponse Prelude.Int
updateWorkspaceResponse_httpStatus :: Lens' UpdateWorkspaceResponse Int
updateWorkspaceResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspaceResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateWorkspaceResponse' :: UpdateWorkspaceResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateWorkspaceResponse
s@UpdateWorkspaceResponse' {} Int
a -> UpdateWorkspaceResponse
s {$sel:httpStatus:UpdateWorkspaceResponse' :: Int
httpStatus = Int
a} :: UpdateWorkspaceResponse)

-- | A structure containing data about the workspace that was created.
updateWorkspaceResponse_workspace :: Lens.Lens' UpdateWorkspaceResponse WorkspaceDescription
updateWorkspaceResponse_workspace :: Lens' UpdateWorkspaceResponse WorkspaceDescription
updateWorkspaceResponse_workspace = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspaceResponse' {WorkspaceDescription
workspace :: WorkspaceDescription
$sel:workspace:UpdateWorkspaceResponse' :: UpdateWorkspaceResponse -> WorkspaceDescription
workspace} -> WorkspaceDescription
workspace) (\s :: UpdateWorkspaceResponse
s@UpdateWorkspaceResponse' {} WorkspaceDescription
a -> UpdateWorkspaceResponse
s {$sel:workspace:UpdateWorkspaceResponse' :: WorkspaceDescription
workspace = WorkspaceDescription
a} :: UpdateWorkspaceResponse)

instance Prelude.NFData UpdateWorkspaceResponse where
  rnf :: UpdateWorkspaceResponse -> ()
rnf UpdateWorkspaceResponse' {Int
WorkspaceDescription
workspace :: WorkspaceDescription
httpStatus :: Int
$sel:workspace:UpdateWorkspaceResponse' :: UpdateWorkspaceResponse -> WorkspaceDescription
$sel:httpStatus:UpdateWorkspaceResponse' :: UpdateWorkspaceResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf WorkspaceDescription
workspace