{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.WorkspaceDescription
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.Grafana.Types.WorkspaceDescription 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.AccountAccessType
import Amazonka.Grafana.Types.AuthenticationSummary
import Amazonka.Grafana.Types.DataSourceType
import Amazonka.Grafana.Types.LicenseType
import Amazonka.Grafana.Types.NotificationDestinationType
import Amazonka.Grafana.Types.PermissionType
import Amazonka.Grafana.Types.VpcConfiguration
import Amazonka.Grafana.Types.WorkspaceStatus
import qualified Amazonka.Prelude as Prelude

-- | A structure containing information about an Amazon Managed Grafana
-- workspace in your account.
--
-- /See:/ 'newWorkspaceDescription' smart constructor.
data WorkspaceDescription = WorkspaceDescription'
  { -- | 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 this is @ORGANIZATION@, the
    -- @workspaceOrganizationalUnits@ parameter specifies which organizational
    -- units the workspace can access.
    WorkspaceDescription -> Maybe AccountAccessType
accountAccessType :: Prelude.Maybe AccountAccessType,
    -- | The user-defined description of the workspace.
    WorkspaceDescription -> Maybe (Sensitive Text)
description :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | Specifies whether this workspace has already fully used its free trial
    -- for Grafana Enterprise.
    WorkspaceDescription -> Maybe Bool
freeTrialConsumed :: Prelude.Maybe Prelude.Bool,
    -- | If this workspace is currently in the free trial period for Grafana
    -- Enterprise, this value specifies when that free trial ends.
    WorkspaceDescription -> Maybe POSIX
freeTrialExpiration :: Prelude.Maybe Data.POSIX,
    -- | If this workspace has a full Grafana Enterprise license, this specifies
    -- when the license ends and will need to be renewed.
    WorkspaceDescription -> Maybe POSIX
licenseExpiration :: Prelude.Maybe Data.POSIX,
    -- | Specifies whether this workspace has a full Grafana Enterprise license
    -- or a free trial license.
    WorkspaceDescription -> Maybe LicenseType
licenseType :: Prelude.Maybe LicenseType,
    -- | The name of the workspace.
    WorkspaceDescription -> Maybe (Sensitive Text)
name :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The Amazon Web Services notification channels that Amazon Managed
    -- Grafana can automatically create IAM roles and permissions for, to allow
    -- Amazon Managed Grafana to use these channels.
    WorkspaceDescription -> Maybe [NotificationDestinationType]
notificationDestinations :: Prelude.Maybe [NotificationDestinationType],
    -- | The name of the IAM role that is used to access resources through
    -- Organizations.
    WorkspaceDescription -> Maybe (Sensitive Text)
organizationRoleName :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | 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.
    WorkspaceDescription -> Maybe (Sensitive [Text])
organizationalUnits :: Prelude.Maybe (Data.Sensitive [Prelude.Text]),
    -- | If this is @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 this is @CUSTOMER_MANAGED@, you 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>
    WorkspaceDescription -> Maybe PermissionType
permissionType :: Prelude.Maybe PermissionType,
    -- | The name of the CloudFormation stack set that is used to generate IAM
    -- roles to be used for this workspace.
    WorkspaceDescription -> Maybe Text
stackSetName :: Prelude.Maybe Prelude.Text,
    -- | The list of tags associated with the workspace.
    WorkspaceDescription -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The configuration for connecting to data sources in a private VPC
    -- (Amazon Virtual Private Cloud).
    WorkspaceDescription -> Maybe VpcConfiguration
vpcConfiguration :: Prelude.Maybe VpcConfiguration,
    -- | The IAM role that grants permissions to the Amazon Web Services
    -- resources that the workspace will view data from. This role must already
    -- exist.
    WorkspaceDescription -> Maybe (Sensitive Text)
workspaceRoleArn :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | A structure that describes whether the workspace uses SAML, IAM Identity
    -- Center, or both methods for user authentication.
    WorkspaceDescription -> AuthenticationSummary
authentication :: AuthenticationSummary,
    -- | The date that the workspace was created.
    WorkspaceDescription -> POSIX
created :: Data.POSIX,
    -- | Specifies the Amazon Web Services data sources that have been configured
    -- to have IAM roles and permissions created to allow Amazon Managed
    -- Grafana to read data from these sources.
    WorkspaceDescription -> [DataSourceType]
dataSources :: [DataSourceType],
    -- | The URL that users can use to access the Grafana console in the
    -- workspace.
    WorkspaceDescription -> Text
endpoint :: Prelude.Text,
    -- | The version of Grafana supported in this workspace.
    WorkspaceDescription -> Text
grafanaVersion :: Prelude.Text,
    -- | The unique ID of this workspace.
    WorkspaceDescription -> Text
id :: Prelude.Text,
    -- | The most recent date that the workspace was modified.
    WorkspaceDescription -> POSIX
modified :: Data.POSIX,
    -- | The current status of the workspace.
    WorkspaceDescription -> WorkspaceStatus
status :: WorkspaceStatus
  }
  deriving (WorkspaceDescription -> WorkspaceDescription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WorkspaceDescription -> WorkspaceDescription -> Bool
$c/= :: WorkspaceDescription -> WorkspaceDescription -> Bool
== :: WorkspaceDescription -> WorkspaceDescription -> Bool
$c== :: WorkspaceDescription -> WorkspaceDescription -> Bool
Prelude.Eq, Int -> WorkspaceDescription -> ShowS
[WorkspaceDescription] -> ShowS
WorkspaceDescription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WorkspaceDescription] -> ShowS
$cshowList :: [WorkspaceDescription] -> ShowS
show :: WorkspaceDescription -> String
$cshow :: WorkspaceDescription -> String
showsPrec :: Int -> WorkspaceDescription -> ShowS
$cshowsPrec :: Int -> WorkspaceDescription -> ShowS
Prelude.Show, forall x. Rep WorkspaceDescription x -> WorkspaceDescription
forall x. WorkspaceDescription -> Rep WorkspaceDescription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WorkspaceDescription x -> WorkspaceDescription
$cfrom :: forall x. WorkspaceDescription -> Rep WorkspaceDescription x
Prelude.Generic)

-- |
-- Create a value of 'WorkspaceDescription' 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', 'workspaceDescription_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 this is @ORGANIZATION@, the
-- @workspaceOrganizationalUnits@ parameter specifies which organizational
-- units the workspace can access.
--
-- 'description', 'workspaceDescription_description' - The user-defined description of the workspace.
--
-- 'freeTrialConsumed', 'workspaceDescription_freeTrialConsumed' - Specifies whether this workspace has already fully used its free trial
-- for Grafana Enterprise.
--
-- 'freeTrialExpiration', 'workspaceDescription_freeTrialExpiration' - If this workspace is currently in the free trial period for Grafana
-- Enterprise, this value specifies when that free trial ends.
--
-- 'licenseExpiration', 'workspaceDescription_licenseExpiration' - If this workspace has a full Grafana Enterprise license, this specifies
-- when the license ends and will need to be renewed.
--
-- 'licenseType', 'workspaceDescription_licenseType' - Specifies whether this workspace has a full Grafana Enterprise license
-- or a free trial license.
--
-- 'name', 'workspaceDescription_name' - The name of the workspace.
--
-- 'notificationDestinations', 'workspaceDescription_notificationDestinations' - The Amazon Web Services notification channels that Amazon Managed
-- Grafana can automatically create IAM roles and permissions for, to allow
-- Amazon Managed Grafana to use these channels.
--
-- 'organizationRoleName', 'workspaceDescription_organizationRoleName' - The name of the IAM role that is used to access resources through
-- Organizations.
--
-- 'organizationalUnits', 'workspaceDescription_organizationalUnits' - 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.
--
-- 'permissionType', 'workspaceDescription_permissionType' - If this is @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 this is @CUSTOMER_MANAGED@, you 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>
--
-- 'stackSetName', 'workspaceDescription_stackSetName' - The name of the CloudFormation stack set that is used to generate IAM
-- roles to be used for this workspace.
--
-- 'tags', 'workspaceDescription_tags' - The list of tags associated with the workspace.
--
-- 'vpcConfiguration', 'workspaceDescription_vpcConfiguration' - The configuration for connecting to data sources in a private VPC
-- (Amazon Virtual Private Cloud).
--
-- 'workspaceRoleArn', 'workspaceDescription_workspaceRoleArn' - The IAM role that grants permissions to the Amazon Web Services
-- resources that the workspace will view data from. This role must already
-- exist.
--
-- 'authentication', 'workspaceDescription_authentication' - A structure that describes whether the workspace uses SAML, IAM Identity
-- Center, or both methods for user authentication.
--
-- 'created', 'workspaceDescription_created' - The date that the workspace was created.
--
-- 'dataSources', 'workspaceDescription_dataSources' - Specifies the Amazon Web Services data sources that have been configured
-- to have IAM roles and permissions created to allow Amazon Managed
-- Grafana to read data from these sources.
--
-- 'endpoint', 'workspaceDescription_endpoint' - The URL that users can use to access the Grafana console in the
-- workspace.
--
-- 'grafanaVersion', 'workspaceDescription_grafanaVersion' - The version of Grafana supported in this workspace.
--
-- 'id', 'workspaceDescription_id' - The unique ID of this workspace.
--
-- 'modified', 'workspaceDescription_modified' - The most recent date that the workspace was modified.
--
-- 'status', 'workspaceDescription_status' - The current status of the workspace.
newWorkspaceDescription ::
  -- | 'authentication'
  AuthenticationSummary ->
  -- | 'created'
  Prelude.UTCTime ->
  -- | 'endpoint'
  Prelude.Text ->
  -- | 'grafanaVersion'
  Prelude.Text ->
  -- | 'id'
  Prelude.Text ->
  -- | 'modified'
  Prelude.UTCTime ->
  -- | 'status'
  WorkspaceStatus ->
  WorkspaceDescription
newWorkspaceDescription :: AuthenticationSummary
-> UTCTime
-> Text
-> Text
-> Text
-> UTCTime
-> WorkspaceStatus
-> WorkspaceDescription
newWorkspaceDescription
  AuthenticationSummary
pAuthentication_
  UTCTime
pCreated_
  Text
pEndpoint_
  Text
pGrafanaVersion_
  Text
pId_
  UTCTime
pModified_
  WorkspaceStatus
pStatus_ =
    WorkspaceDescription'
      { $sel:accountAccessType:WorkspaceDescription' :: Maybe AccountAccessType
accountAccessType =
          forall a. Maybe a
Prelude.Nothing,
        $sel:description:WorkspaceDescription' :: Maybe (Sensitive Text)
description = forall a. Maybe a
Prelude.Nothing,
        $sel:freeTrialConsumed:WorkspaceDescription' :: Maybe Bool
freeTrialConsumed = forall a. Maybe a
Prelude.Nothing,
        $sel:freeTrialExpiration:WorkspaceDescription' :: Maybe POSIX
freeTrialExpiration = forall a. Maybe a
Prelude.Nothing,
        $sel:licenseExpiration:WorkspaceDescription' :: Maybe POSIX
licenseExpiration = forall a. Maybe a
Prelude.Nothing,
        $sel:licenseType:WorkspaceDescription' :: Maybe LicenseType
licenseType = forall a. Maybe a
Prelude.Nothing,
        $sel:name:WorkspaceDescription' :: Maybe (Sensitive Text)
name = forall a. Maybe a
Prelude.Nothing,
        $sel:notificationDestinations:WorkspaceDescription' :: Maybe [NotificationDestinationType]
notificationDestinations = forall a. Maybe a
Prelude.Nothing,
        $sel:organizationRoleName:WorkspaceDescription' :: Maybe (Sensitive Text)
organizationRoleName = forall a. Maybe a
Prelude.Nothing,
        $sel:organizationalUnits:WorkspaceDescription' :: Maybe (Sensitive [Text])
organizationalUnits = forall a. Maybe a
Prelude.Nothing,
        $sel:permissionType:WorkspaceDescription' :: Maybe PermissionType
permissionType = forall a. Maybe a
Prelude.Nothing,
        $sel:stackSetName:WorkspaceDescription' :: Maybe Text
stackSetName = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:WorkspaceDescription' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:vpcConfiguration:WorkspaceDescription' :: Maybe VpcConfiguration
vpcConfiguration = forall a. Maybe a
Prelude.Nothing,
        $sel:workspaceRoleArn:WorkspaceDescription' :: Maybe (Sensitive Text)
workspaceRoleArn = forall a. Maybe a
Prelude.Nothing,
        $sel:authentication:WorkspaceDescription' :: AuthenticationSummary
authentication = AuthenticationSummary
pAuthentication_,
        $sel:created:WorkspaceDescription' :: POSIX
created = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreated_,
        $sel:dataSources:WorkspaceDescription' :: [DataSourceType]
dataSources = forall a. Monoid a => a
Prelude.mempty,
        $sel:endpoint:WorkspaceDescription' :: Text
endpoint = Text
pEndpoint_,
        $sel:grafanaVersion:WorkspaceDescription' :: Text
grafanaVersion = Text
pGrafanaVersion_,
        $sel:id:WorkspaceDescription' :: Text
id = Text
pId_,
        $sel:modified:WorkspaceDescription' :: POSIX
modified = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pModified_,
        $sel:status:WorkspaceDescription' :: WorkspaceStatus
status = WorkspaceStatus
pStatus_
      }

-- | 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 this is @ORGANIZATION@, the
-- @workspaceOrganizationalUnits@ parameter specifies which organizational
-- units the workspace can access.
workspaceDescription_accountAccessType :: Lens.Lens' WorkspaceDescription (Prelude.Maybe AccountAccessType)
workspaceDescription_accountAccessType :: Lens' WorkspaceDescription (Maybe AccountAccessType)
workspaceDescription_accountAccessType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\WorkspaceDescription' {Maybe AccountAccessType
accountAccessType :: Maybe AccountAccessType
$sel:accountAccessType:WorkspaceDescription' :: WorkspaceDescription -> Maybe AccountAccessType
accountAccessType} -> Maybe AccountAccessType
accountAccessType) (\s :: WorkspaceDescription
s@WorkspaceDescription' {} Maybe AccountAccessType
a -> WorkspaceDescription
s {$sel:accountAccessType:WorkspaceDescription' :: Maybe AccountAccessType
accountAccessType = Maybe AccountAccessType
a} :: WorkspaceDescription)

-- | The user-defined description of the workspace.
workspaceDescription_description :: Lens.Lens' WorkspaceDescription (Prelude.Maybe Prelude.Text)
workspaceDescription_description :: Lens' WorkspaceDescription (Maybe Text)
workspaceDescription_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\WorkspaceDescription' {Maybe (Sensitive Text)
description :: Maybe (Sensitive Text)
$sel:description:WorkspaceDescription' :: WorkspaceDescription -> Maybe (Sensitive Text)
description} -> Maybe (Sensitive Text)
description) (\s :: WorkspaceDescription
s@WorkspaceDescription' {} Maybe (Sensitive Text)
a -> WorkspaceDescription
s {$sel:description:WorkspaceDescription' :: Maybe (Sensitive Text)
description = Maybe (Sensitive Text)
a} :: WorkspaceDescription) 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

-- | Specifies whether this workspace has already fully used its free trial
-- for Grafana Enterprise.
workspaceDescription_freeTrialConsumed :: Lens.Lens' WorkspaceDescription (Prelude.Maybe Prelude.Bool)
workspaceDescription_freeTrialConsumed :: Lens' WorkspaceDescription (Maybe Bool)
workspaceDescription_freeTrialConsumed = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\WorkspaceDescription' {Maybe Bool
freeTrialConsumed :: Maybe Bool
$sel:freeTrialConsumed:WorkspaceDescription' :: WorkspaceDescription -> Maybe Bool
freeTrialConsumed} -> Maybe Bool
freeTrialConsumed) (\s :: WorkspaceDescription
s@WorkspaceDescription' {} Maybe Bool
a -> WorkspaceDescription
s {$sel:freeTrialConsumed:WorkspaceDescription' :: Maybe Bool
freeTrialConsumed = Maybe Bool
a} :: WorkspaceDescription)

-- | If this workspace is currently in the free trial period for Grafana
-- Enterprise, this value specifies when that free trial ends.
workspaceDescription_freeTrialExpiration :: Lens.Lens' WorkspaceDescription (Prelude.Maybe Prelude.UTCTime)
workspaceDescription_freeTrialExpiration :: Lens' WorkspaceDescription (Maybe UTCTime)
workspaceDescription_freeTrialExpiration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\WorkspaceDescription' {Maybe POSIX
freeTrialExpiration :: Maybe POSIX
$sel:freeTrialExpiration:WorkspaceDescription' :: WorkspaceDescription -> Maybe POSIX
freeTrialExpiration} -> Maybe POSIX
freeTrialExpiration) (\s :: WorkspaceDescription
s@WorkspaceDescription' {} Maybe POSIX
a -> WorkspaceDescription
s {$sel:freeTrialExpiration:WorkspaceDescription' :: Maybe POSIX
freeTrialExpiration = Maybe POSIX
a} :: WorkspaceDescription) 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 :: Format). Iso' (Time a) UTCTime
Data._Time

-- | If this workspace has a full Grafana Enterprise license, this specifies
-- when the license ends and will need to be renewed.
workspaceDescription_licenseExpiration :: Lens.Lens' WorkspaceDescription (Prelude.Maybe Prelude.UTCTime)
workspaceDescription_licenseExpiration :: Lens' WorkspaceDescription (Maybe UTCTime)
workspaceDescription_licenseExpiration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\WorkspaceDescription' {Maybe POSIX
licenseExpiration :: Maybe POSIX
$sel:licenseExpiration:WorkspaceDescription' :: WorkspaceDescription -> Maybe POSIX
licenseExpiration} -> Maybe POSIX
licenseExpiration) (\s :: WorkspaceDescription
s@WorkspaceDescription' {} Maybe POSIX
a -> WorkspaceDescription
s {$sel:licenseExpiration:WorkspaceDescription' :: Maybe POSIX
licenseExpiration = Maybe POSIX
a} :: WorkspaceDescription) 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 :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Specifies whether this workspace has a full Grafana Enterprise license
-- or a free trial license.
workspaceDescription_licenseType :: Lens.Lens' WorkspaceDescription (Prelude.Maybe LicenseType)
workspaceDescription_licenseType :: Lens' WorkspaceDescription (Maybe LicenseType)
workspaceDescription_licenseType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\WorkspaceDescription' {Maybe LicenseType
licenseType :: Maybe LicenseType
$sel:licenseType:WorkspaceDescription' :: WorkspaceDescription -> Maybe LicenseType
licenseType} -> Maybe LicenseType
licenseType) (\s :: WorkspaceDescription
s@WorkspaceDescription' {} Maybe LicenseType
a -> WorkspaceDescription
s {$sel:licenseType:WorkspaceDescription' :: Maybe LicenseType
licenseType = Maybe LicenseType
a} :: WorkspaceDescription)

-- | The name of the workspace.
workspaceDescription_name :: Lens.Lens' WorkspaceDescription (Prelude.Maybe Prelude.Text)
workspaceDescription_name :: Lens' WorkspaceDescription (Maybe Text)
workspaceDescription_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\WorkspaceDescription' {Maybe (Sensitive Text)
name :: Maybe (Sensitive Text)
$sel:name:WorkspaceDescription' :: WorkspaceDescription -> Maybe (Sensitive Text)
name} -> Maybe (Sensitive Text)
name) (\s :: WorkspaceDescription
s@WorkspaceDescription' {} Maybe (Sensitive Text)
a -> WorkspaceDescription
s {$sel:name:WorkspaceDescription' :: Maybe (Sensitive Text)
name = Maybe (Sensitive Text)
a} :: WorkspaceDescription) 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 Amazon Web Services notification channels that Amazon Managed
-- Grafana can automatically create IAM roles and permissions for, to allow
-- Amazon Managed Grafana to use these channels.
workspaceDescription_notificationDestinations :: Lens.Lens' WorkspaceDescription (Prelude.Maybe [NotificationDestinationType])
workspaceDescription_notificationDestinations :: Lens' WorkspaceDescription (Maybe [NotificationDestinationType])
workspaceDescription_notificationDestinations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\WorkspaceDescription' {Maybe [NotificationDestinationType]
notificationDestinations :: Maybe [NotificationDestinationType]
$sel:notificationDestinations:WorkspaceDescription' :: WorkspaceDescription -> Maybe [NotificationDestinationType]
notificationDestinations} -> Maybe [NotificationDestinationType]
notificationDestinations) (\s :: WorkspaceDescription
s@WorkspaceDescription' {} Maybe [NotificationDestinationType]
a -> WorkspaceDescription
s {$sel:notificationDestinations:WorkspaceDescription' :: Maybe [NotificationDestinationType]
notificationDestinations = Maybe [NotificationDestinationType]
a} :: WorkspaceDescription) 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

-- | The name of the IAM role that is used to access resources through
-- Organizations.
workspaceDescription_organizationRoleName :: Lens.Lens' WorkspaceDescription (Prelude.Maybe Prelude.Text)
workspaceDescription_organizationRoleName :: Lens' WorkspaceDescription (Maybe Text)
workspaceDescription_organizationRoleName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\WorkspaceDescription' {Maybe (Sensitive Text)
organizationRoleName :: Maybe (Sensitive Text)
$sel:organizationRoleName:WorkspaceDescription' :: WorkspaceDescription -> Maybe (Sensitive Text)
organizationRoleName} -> Maybe (Sensitive Text)
organizationRoleName) (\s :: WorkspaceDescription
s@WorkspaceDescription' {} Maybe (Sensitive Text)
a -> WorkspaceDescription
s {$sel:organizationRoleName:WorkspaceDescription' :: Maybe (Sensitive Text)
organizationRoleName = Maybe (Sensitive Text)
a} :: WorkspaceDescription) 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

-- | 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.
workspaceDescription_organizationalUnits :: Lens.Lens' WorkspaceDescription (Prelude.Maybe [Prelude.Text])
workspaceDescription_organizationalUnits :: Lens' WorkspaceDescription (Maybe [Text])
workspaceDescription_organizationalUnits = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\WorkspaceDescription' {Maybe (Sensitive [Text])
organizationalUnits :: Maybe (Sensitive [Text])
$sel:organizationalUnits:WorkspaceDescription' :: WorkspaceDescription -> Maybe (Sensitive [Text])
organizationalUnits} -> Maybe (Sensitive [Text])
organizationalUnits) (\s :: WorkspaceDescription
s@WorkspaceDescription' {} Maybe (Sensitive [Text])
a -> WorkspaceDescription
s {$sel:organizationalUnits:WorkspaceDescription' :: Maybe (Sensitive [Text])
organizationalUnits = Maybe (Sensitive [Text])
a} :: WorkspaceDescription) 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)

-- | If this is @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 this is @CUSTOMER_MANAGED@, you 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>
workspaceDescription_permissionType :: Lens.Lens' WorkspaceDescription (Prelude.Maybe PermissionType)
workspaceDescription_permissionType :: Lens' WorkspaceDescription (Maybe PermissionType)
workspaceDescription_permissionType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\WorkspaceDescription' {Maybe PermissionType
permissionType :: Maybe PermissionType
$sel:permissionType:WorkspaceDescription' :: WorkspaceDescription -> Maybe PermissionType
permissionType} -> Maybe PermissionType
permissionType) (\s :: WorkspaceDescription
s@WorkspaceDescription' {} Maybe PermissionType
a -> WorkspaceDescription
s {$sel:permissionType:WorkspaceDescription' :: Maybe PermissionType
permissionType = Maybe PermissionType
a} :: WorkspaceDescription)

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

-- | The list of tags associated with the workspace.
workspaceDescription_tags :: Lens.Lens' WorkspaceDescription (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
workspaceDescription_tags :: Lens' WorkspaceDescription (Maybe (HashMap Text Text))
workspaceDescription_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\WorkspaceDescription' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:WorkspaceDescription' :: WorkspaceDescription -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: WorkspaceDescription
s@WorkspaceDescription' {} Maybe (HashMap Text Text)
a -> WorkspaceDescription
s {$sel:tags:WorkspaceDescription' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: WorkspaceDescription) 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

-- | The configuration for connecting to data sources in a private VPC
-- (Amazon Virtual Private Cloud).
workspaceDescription_vpcConfiguration :: Lens.Lens' WorkspaceDescription (Prelude.Maybe VpcConfiguration)
workspaceDescription_vpcConfiguration :: Lens' WorkspaceDescription (Maybe VpcConfiguration)
workspaceDescription_vpcConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\WorkspaceDescription' {Maybe VpcConfiguration
vpcConfiguration :: Maybe VpcConfiguration
$sel:vpcConfiguration:WorkspaceDescription' :: WorkspaceDescription -> Maybe VpcConfiguration
vpcConfiguration} -> Maybe VpcConfiguration
vpcConfiguration) (\s :: WorkspaceDescription
s@WorkspaceDescription' {} Maybe VpcConfiguration
a -> WorkspaceDescription
s {$sel:vpcConfiguration:WorkspaceDescription' :: Maybe VpcConfiguration
vpcConfiguration = Maybe VpcConfiguration
a} :: WorkspaceDescription)

-- | The IAM role that grants permissions to the Amazon Web Services
-- resources that the workspace will view data from. This role must already
-- exist.
workspaceDescription_workspaceRoleArn :: Lens.Lens' WorkspaceDescription (Prelude.Maybe Prelude.Text)
workspaceDescription_workspaceRoleArn :: Lens' WorkspaceDescription (Maybe Text)
workspaceDescription_workspaceRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\WorkspaceDescription' {Maybe (Sensitive Text)
workspaceRoleArn :: Maybe (Sensitive Text)
$sel:workspaceRoleArn:WorkspaceDescription' :: WorkspaceDescription -> Maybe (Sensitive Text)
workspaceRoleArn} -> Maybe (Sensitive Text)
workspaceRoleArn) (\s :: WorkspaceDescription
s@WorkspaceDescription' {} Maybe (Sensitive Text)
a -> WorkspaceDescription
s {$sel:workspaceRoleArn:WorkspaceDescription' :: Maybe (Sensitive Text)
workspaceRoleArn = Maybe (Sensitive Text)
a} :: WorkspaceDescription) 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 structure that describes whether the workspace uses SAML, IAM Identity
-- Center, or both methods for user authentication.
workspaceDescription_authentication :: Lens.Lens' WorkspaceDescription AuthenticationSummary
workspaceDescription_authentication :: Lens' WorkspaceDescription AuthenticationSummary
workspaceDescription_authentication = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\WorkspaceDescription' {AuthenticationSummary
authentication :: AuthenticationSummary
$sel:authentication:WorkspaceDescription' :: WorkspaceDescription -> AuthenticationSummary
authentication} -> AuthenticationSummary
authentication) (\s :: WorkspaceDescription
s@WorkspaceDescription' {} AuthenticationSummary
a -> WorkspaceDescription
s {$sel:authentication:WorkspaceDescription' :: AuthenticationSummary
authentication = AuthenticationSummary
a} :: WorkspaceDescription)

-- | The date that the workspace was created.
workspaceDescription_created :: Lens.Lens' WorkspaceDescription Prelude.UTCTime
workspaceDescription_created :: Lens' WorkspaceDescription UTCTime
workspaceDescription_created = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\WorkspaceDescription' {POSIX
created :: POSIX
$sel:created:WorkspaceDescription' :: WorkspaceDescription -> POSIX
created} -> POSIX
created) (\s :: WorkspaceDescription
s@WorkspaceDescription' {} POSIX
a -> WorkspaceDescription
s {$sel:created:WorkspaceDescription' :: POSIX
created = POSIX
a} :: WorkspaceDescription) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Specifies the Amazon Web Services data sources that have been configured
-- to have IAM roles and permissions created to allow Amazon Managed
-- Grafana to read data from these sources.
workspaceDescription_dataSources :: Lens.Lens' WorkspaceDescription [DataSourceType]
workspaceDescription_dataSources :: Lens' WorkspaceDescription [DataSourceType]
workspaceDescription_dataSources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\WorkspaceDescription' {[DataSourceType]
dataSources :: [DataSourceType]
$sel:dataSources:WorkspaceDescription' :: WorkspaceDescription -> [DataSourceType]
dataSources} -> [DataSourceType]
dataSources) (\s :: WorkspaceDescription
s@WorkspaceDescription' {} [DataSourceType]
a -> WorkspaceDescription
s {$sel:dataSources:WorkspaceDescription' :: [DataSourceType]
dataSources = [DataSourceType]
a} :: WorkspaceDescription) 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 URL that users can use to access the Grafana console in the
-- workspace.
workspaceDescription_endpoint :: Lens.Lens' WorkspaceDescription Prelude.Text
workspaceDescription_endpoint :: Lens' WorkspaceDescription Text
workspaceDescription_endpoint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\WorkspaceDescription' {Text
endpoint :: Text
$sel:endpoint:WorkspaceDescription' :: WorkspaceDescription -> Text
endpoint} -> Text
endpoint) (\s :: WorkspaceDescription
s@WorkspaceDescription' {} Text
a -> WorkspaceDescription
s {$sel:endpoint:WorkspaceDescription' :: Text
endpoint = Text
a} :: WorkspaceDescription)

-- | The version of Grafana supported in this workspace.
workspaceDescription_grafanaVersion :: Lens.Lens' WorkspaceDescription Prelude.Text
workspaceDescription_grafanaVersion :: Lens' WorkspaceDescription Text
workspaceDescription_grafanaVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\WorkspaceDescription' {Text
grafanaVersion :: Text
$sel:grafanaVersion:WorkspaceDescription' :: WorkspaceDescription -> Text
grafanaVersion} -> Text
grafanaVersion) (\s :: WorkspaceDescription
s@WorkspaceDescription' {} Text
a -> WorkspaceDescription
s {$sel:grafanaVersion:WorkspaceDescription' :: Text
grafanaVersion = Text
a} :: WorkspaceDescription)

-- | The unique ID of this workspace.
workspaceDescription_id :: Lens.Lens' WorkspaceDescription Prelude.Text
workspaceDescription_id :: Lens' WorkspaceDescription Text
workspaceDescription_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\WorkspaceDescription' {Text
id :: Text
$sel:id:WorkspaceDescription' :: WorkspaceDescription -> Text
id} -> Text
id) (\s :: WorkspaceDescription
s@WorkspaceDescription' {} Text
a -> WorkspaceDescription
s {$sel:id:WorkspaceDescription' :: Text
id = Text
a} :: WorkspaceDescription)

-- | The most recent date that the workspace was modified.
workspaceDescription_modified :: Lens.Lens' WorkspaceDescription Prelude.UTCTime
workspaceDescription_modified :: Lens' WorkspaceDescription UTCTime
workspaceDescription_modified = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\WorkspaceDescription' {POSIX
modified :: POSIX
$sel:modified:WorkspaceDescription' :: WorkspaceDescription -> POSIX
modified} -> POSIX
modified) (\s :: WorkspaceDescription
s@WorkspaceDescription' {} POSIX
a -> WorkspaceDescription
s {$sel:modified:WorkspaceDescription' :: POSIX
modified = POSIX
a} :: WorkspaceDescription) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The current status of the workspace.
workspaceDescription_status :: Lens.Lens' WorkspaceDescription WorkspaceStatus
workspaceDescription_status :: Lens' WorkspaceDescription WorkspaceStatus
workspaceDescription_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\WorkspaceDescription' {WorkspaceStatus
status :: WorkspaceStatus
$sel:status:WorkspaceDescription' :: WorkspaceDescription -> WorkspaceStatus
status} -> WorkspaceStatus
status) (\s :: WorkspaceDescription
s@WorkspaceDescription' {} WorkspaceStatus
a -> WorkspaceDescription
s {$sel:status:WorkspaceDescription' :: WorkspaceStatus
status = WorkspaceStatus
a} :: WorkspaceDescription)

instance Data.FromJSON WorkspaceDescription where
  parseJSON :: Value -> Parser WorkspaceDescription
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"WorkspaceDescription"
      ( \Object
x ->
          Maybe AccountAccessType
-> Maybe (Sensitive Text)
-> Maybe Bool
-> Maybe POSIX
-> Maybe POSIX
-> Maybe LicenseType
-> Maybe (Sensitive Text)
-> Maybe [NotificationDestinationType]
-> Maybe (Sensitive Text)
-> Maybe (Sensitive [Text])
-> Maybe PermissionType
-> Maybe Text
-> Maybe (HashMap Text Text)
-> Maybe VpcConfiguration
-> Maybe (Sensitive Text)
-> AuthenticationSummary
-> POSIX
-> [DataSourceType]
-> Text
-> Text
-> Text
-> POSIX
-> WorkspaceStatus
-> WorkspaceDescription
WorkspaceDescription'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"accountAccessType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"description")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"freeTrialConsumed")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"freeTrialExpiration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"licenseExpiration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"licenseType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"name")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"notificationDestinations"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"organizationRoleName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"organizationalUnits"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"permissionType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"stackSetName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"tags" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"vpcConfiguration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"workspaceRoleArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"authentication")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"created")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"dataSources" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"endpoint")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"grafanaVersion")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"id")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"modified")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"status")
      )

instance Prelude.Hashable WorkspaceDescription where
  hashWithSalt :: Int -> WorkspaceDescription -> Int
hashWithSalt Int
_salt WorkspaceDescription' {[DataSourceType]
Maybe Bool
Maybe [NotificationDestinationType]
Maybe Text
Maybe (HashMap Text Text)
Maybe (Sensitive [Text])
Maybe (Sensitive Text)
Maybe POSIX
Maybe AccountAccessType
Maybe LicenseType
Maybe PermissionType
Maybe VpcConfiguration
Text
POSIX
AuthenticationSummary
WorkspaceStatus
status :: WorkspaceStatus
modified :: POSIX
id :: Text
grafanaVersion :: Text
endpoint :: Text
dataSources :: [DataSourceType]
created :: POSIX
authentication :: AuthenticationSummary
workspaceRoleArn :: Maybe (Sensitive Text)
vpcConfiguration :: Maybe VpcConfiguration
tags :: Maybe (HashMap Text Text)
stackSetName :: Maybe Text
permissionType :: Maybe PermissionType
organizationalUnits :: Maybe (Sensitive [Text])
organizationRoleName :: Maybe (Sensitive Text)
notificationDestinations :: Maybe [NotificationDestinationType]
name :: Maybe (Sensitive Text)
licenseType :: Maybe LicenseType
licenseExpiration :: Maybe POSIX
freeTrialExpiration :: Maybe POSIX
freeTrialConsumed :: Maybe Bool
description :: Maybe (Sensitive Text)
accountAccessType :: Maybe AccountAccessType
$sel:status:WorkspaceDescription' :: WorkspaceDescription -> WorkspaceStatus
$sel:modified:WorkspaceDescription' :: WorkspaceDescription -> POSIX
$sel:id:WorkspaceDescription' :: WorkspaceDescription -> Text
$sel:grafanaVersion:WorkspaceDescription' :: WorkspaceDescription -> Text
$sel:endpoint:WorkspaceDescription' :: WorkspaceDescription -> Text
$sel:dataSources:WorkspaceDescription' :: WorkspaceDescription -> [DataSourceType]
$sel:created:WorkspaceDescription' :: WorkspaceDescription -> POSIX
$sel:authentication:WorkspaceDescription' :: WorkspaceDescription -> AuthenticationSummary
$sel:workspaceRoleArn:WorkspaceDescription' :: WorkspaceDescription -> Maybe (Sensitive Text)
$sel:vpcConfiguration:WorkspaceDescription' :: WorkspaceDescription -> Maybe VpcConfiguration
$sel:tags:WorkspaceDescription' :: WorkspaceDescription -> Maybe (HashMap Text Text)
$sel:stackSetName:WorkspaceDescription' :: WorkspaceDescription -> Maybe Text
$sel:permissionType:WorkspaceDescription' :: WorkspaceDescription -> Maybe PermissionType
$sel:organizationalUnits:WorkspaceDescription' :: WorkspaceDescription -> Maybe (Sensitive [Text])
$sel:organizationRoleName:WorkspaceDescription' :: WorkspaceDescription -> Maybe (Sensitive Text)
$sel:notificationDestinations:WorkspaceDescription' :: WorkspaceDescription -> Maybe [NotificationDestinationType]
$sel:name:WorkspaceDescription' :: WorkspaceDescription -> Maybe (Sensitive Text)
$sel:licenseType:WorkspaceDescription' :: WorkspaceDescription -> Maybe LicenseType
$sel:licenseExpiration:WorkspaceDescription' :: WorkspaceDescription -> Maybe POSIX
$sel:freeTrialExpiration:WorkspaceDescription' :: WorkspaceDescription -> Maybe POSIX
$sel:freeTrialConsumed:WorkspaceDescription' :: WorkspaceDescription -> Maybe Bool
$sel:description:WorkspaceDescription' :: WorkspaceDescription -> Maybe (Sensitive Text)
$sel:accountAccessType:WorkspaceDescription' :: WorkspaceDescription -> 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)
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
freeTrialConsumed
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
freeTrialExpiration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
licenseExpiration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LicenseType
licenseType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [NotificationDestinationType]
notificationDestinations
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
organizationRoleName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive [Text])
organizationalUnits
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PermissionType
permissionType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
stackSetName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VpcConfiguration
vpcConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
workspaceRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` AuthenticationSummary
authentication
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
created
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [DataSourceType]
dataSources
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
endpoint
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
grafanaVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
modified
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` WorkspaceStatus
status

instance Prelude.NFData WorkspaceDescription where
  rnf :: WorkspaceDescription -> ()
rnf WorkspaceDescription' {[DataSourceType]
Maybe Bool
Maybe [NotificationDestinationType]
Maybe Text
Maybe (HashMap Text Text)
Maybe (Sensitive [Text])
Maybe (Sensitive Text)
Maybe POSIX
Maybe AccountAccessType
Maybe LicenseType
Maybe PermissionType
Maybe VpcConfiguration
Text
POSIX
AuthenticationSummary
WorkspaceStatus
status :: WorkspaceStatus
modified :: POSIX
id :: Text
grafanaVersion :: Text
endpoint :: Text
dataSources :: [DataSourceType]
created :: POSIX
authentication :: AuthenticationSummary
workspaceRoleArn :: Maybe (Sensitive Text)
vpcConfiguration :: Maybe VpcConfiguration
tags :: Maybe (HashMap Text Text)
stackSetName :: Maybe Text
permissionType :: Maybe PermissionType
organizationalUnits :: Maybe (Sensitive [Text])
organizationRoleName :: Maybe (Sensitive Text)
notificationDestinations :: Maybe [NotificationDestinationType]
name :: Maybe (Sensitive Text)
licenseType :: Maybe LicenseType
licenseExpiration :: Maybe POSIX
freeTrialExpiration :: Maybe POSIX
freeTrialConsumed :: Maybe Bool
description :: Maybe (Sensitive Text)
accountAccessType :: Maybe AccountAccessType
$sel:status:WorkspaceDescription' :: WorkspaceDescription -> WorkspaceStatus
$sel:modified:WorkspaceDescription' :: WorkspaceDescription -> POSIX
$sel:id:WorkspaceDescription' :: WorkspaceDescription -> Text
$sel:grafanaVersion:WorkspaceDescription' :: WorkspaceDescription -> Text
$sel:endpoint:WorkspaceDescription' :: WorkspaceDescription -> Text
$sel:dataSources:WorkspaceDescription' :: WorkspaceDescription -> [DataSourceType]
$sel:created:WorkspaceDescription' :: WorkspaceDescription -> POSIX
$sel:authentication:WorkspaceDescription' :: WorkspaceDescription -> AuthenticationSummary
$sel:workspaceRoleArn:WorkspaceDescription' :: WorkspaceDescription -> Maybe (Sensitive Text)
$sel:vpcConfiguration:WorkspaceDescription' :: WorkspaceDescription -> Maybe VpcConfiguration
$sel:tags:WorkspaceDescription' :: WorkspaceDescription -> Maybe (HashMap Text Text)
$sel:stackSetName:WorkspaceDescription' :: WorkspaceDescription -> Maybe Text
$sel:permissionType:WorkspaceDescription' :: WorkspaceDescription -> Maybe PermissionType
$sel:organizationalUnits:WorkspaceDescription' :: WorkspaceDescription -> Maybe (Sensitive [Text])
$sel:organizationRoleName:WorkspaceDescription' :: WorkspaceDescription -> Maybe (Sensitive Text)
$sel:notificationDestinations:WorkspaceDescription' :: WorkspaceDescription -> Maybe [NotificationDestinationType]
$sel:name:WorkspaceDescription' :: WorkspaceDescription -> Maybe (Sensitive Text)
$sel:licenseType:WorkspaceDescription' :: WorkspaceDescription -> Maybe LicenseType
$sel:licenseExpiration:WorkspaceDescription' :: WorkspaceDescription -> Maybe POSIX
$sel:freeTrialExpiration:WorkspaceDescription' :: WorkspaceDescription -> Maybe POSIX
$sel:freeTrialConsumed:WorkspaceDescription' :: WorkspaceDescription -> Maybe Bool
$sel:description:WorkspaceDescription' :: WorkspaceDescription -> Maybe (Sensitive Text)
$sel:accountAccessType:WorkspaceDescription' :: WorkspaceDescription -> 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)
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
freeTrialConsumed
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
freeTrialExpiration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
licenseExpiration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LicenseType
licenseType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [NotificationDestinationType]
notificationDestinations
      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 (Sensitive [Text])
organizationalUnits
      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 Text
stackSetName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      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 (Sensitive Text)
workspaceRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf AuthenticationSummary
authentication
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
created
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [DataSourceType]
dataSources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
endpoint
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
grafanaVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
modified
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf WorkspaceStatus
status