{-# 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.Config.Types.OrganizationCustomPolicyRuleMetadata
-- 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.Config.Types.OrganizationCustomPolicyRuleMetadata where

import Amazonka.Config.Types.MaximumExecutionFrequency
import Amazonka.Config.Types.OrganizationConfigRuleTriggerTypeNoSN
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | An object that specifies metadata for your organization\'s Config Custom
-- Policy rule. The metadata includes the runtime system in use, which
-- accounts have debug logging enabled, and other custom rule metadata,
-- such as resource type, resource ID of Amazon Web Services resource, and
-- organization trigger types that initiate Config to evaluate Amazon Web
-- Services resources against a rule.
--
-- /See:/ 'newOrganizationCustomPolicyRuleMetadata' smart constructor.
data OrganizationCustomPolicyRuleMetadata = OrganizationCustomPolicyRuleMetadata'
  { -- | A list of accounts that you can enable debug logging for your
    -- organization Config Custom Policy rule. List is null when debug logging
    -- is enabled for all accounts.
    OrganizationCustomPolicyRuleMetadata -> Maybe [Text]
debugLogDeliveryAccounts :: Prelude.Maybe [Prelude.Text],
    -- | The description that you provide for your organization Config Custom
    -- Policy rule.
    OrganizationCustomPolicyRuleMetadata -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | A string, in JSON format, that is passed to your organization Config
    -- Custom Policy rule.
    OrganizationCustomPolicyRuleMetadata -> Maybe Text
inputParameters :: Prelude.Maybe Prelude.Text,
    -- | The maximum frequency with which Config runs evaluations for a rule.
    -- Your Config Custom Policy rule is triggered when Config delivers the
    -- configuration snapshot. For more information, see
    -- ConfigSnapshotDeliveryProperties.
    OrganizationCustomPolicyRuleMetadata
-> Maybe MaximumExecutionFrequency
maximumExecutionFrequency :: Prelude.Maybe MaximumExecutionFrequency,
    -- | The type of notification that initiates Config to run an evaluation for
    -- a rule. For Config Custom Policy rules, Config supports change-initiated
    -- notification types:
    --
    -- -   @ConfigurationItemChangeNotification@ - Initiates an evaluation when
    --     Config delivers a configuration item as a result of a resource
    --     change.
    --
    -- -   @OversizedConfigurationItemChangeNotification@ - Initiates an
    --     evaluation when Config delivers an oversized configuration item.
    --     Config may generate this notification type when a resource changes
    --     and the notification exceeds the maximum size allowed by Amazon SNS.
    OrganizationCustomPolicyRuleMetadata
-> Maybe [OrganizationConfigRuleTriggerTypeNoSN]
organizationConfigRuleTriggerTypes :: Prelude.Maybe [OrganizationConfigRuleTriggerTypeNoSN],
    -- | The ID of the Amazon Web Services resource that was evaluated.
    OrganizationCustomPolicyRuleMetadata -> Maybe Text
resourceIdScope :: Prelude.Maybe Prelude.Text,
    -- | The type of the Amazon Web Services resource that was evaluated.
    OrganizationCustomPolicyRuleMetadata -> Maybe [Text]
resourceTypesScope :: Prelude.Maybe [Prelude.Text],
    -- | One part of a key-value pair that make up a tag. A key is a general
    -- label that acts like a category for more specific tag values.
    OrganizationCustomPolicyRuleMetadata -> Maybe Text
tagKeyScope :: Prelude.Maybe Prelude.Text,
    -- | The optional part of a key-value pair that make up a tag. A value acts
    -- as a descriptor within a tag category (key).
    OrganizationCustomPolicyRuleMetadata -> Maybe Text
tagValueScope :: Prelude.Maybe Prelude.Text,
    -- | The runtime system for your organization Config Custom Policy rules.
    -- Guard is a policy-as-code language that allows you to write policies
    -- that are enforced by Config Custom Policy rules. For more information
    -- about Guard, see the
    -- <https://github.com/aws-cloudformation/cloudformation-guard Guard GitHub Repository>.
    OrganizationCustomPolicyRuleMetadata -> Text
policyRuntime :: Prelude.Text,
    -- | The policy definition containing the logic for your organization Config
    -- Custom Policy rule.
    OrganizationCustomPolicyRuleMetadata -> Text
policyText :: Prelude.Text
  }
  deriving (OrganizationCustomPolicyRuleMetadata
-> OrganizationCustomPolicyRuleMetadata -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OrganizationCustomPolicyRuleMetadata
-> OrganizationCustomPolicyRuleMetadata -> Bool
$c/= :: OrganizationCustomPolicyRuleMetadata
-> OrganizationCustomPolicyRuleMetadata -> Bool
== :: OrganizationCustomPolicyRuleMetadata
-> OrganizationCustomPolicyRuleMetadata -> Bool
$c== :: OrganizationCustomPolicyRuleMetadata
-> OrganizationCustomPolicyRuleMetadata -> Bool
Prelude.Eq, ReadPrec [OrganizationCustomPolicyRuleMetadata]
ReadPrec OrganizationCustomPolicyRuleMetadata
Int -> ReadS OrganizationCustomPolicyRuleMetadata
ReadS [OrganizationCustomPolicyRuleMetadata]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OrganizationCustomPolicyRuleMetadata]
$creadListPrec :: ReadPrec [OrganizationCustomPolicyRuleMetadata]
readPrec :: ReadPrec OrganizationCustomPolicyRuleMetadata
$creadPrec :: ReadPrec OrganizationCustomPolicyRuleMetadata
readList :: ReadS [OrganizationCustomPolicyRuleMetadata]
$creadList :: ReadS [OrganizationCustomPolicyRuleMetadata]
readsPrec :: Int -> ReadS OrganizationCustomPolicyRuleMetadata
$creadsPrec :: Int -> ReadS OrganizationCustomPolicyRuleMetadata
Prelude.Read, Int -> OrganizationCustomPolicyRuleMetadata -> ShowS
[OrganizationCustomPolicyRuleMetadata] -> ShowS
OrganizationCustomPolicyRuleMetadata -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OrganizationCustomPolicyRuleMetadata] -> ShowS
$cshowList :: [OrganizationCustomPolicyRuleMetadata] -> ShowS
show :: OrganizationCustomPolicyRuleMetadata -> String
$cshow :: OrganizationCustomPolicyRuleMetadata -> String
showsPrec :: Int -> OrganizationCustomPolicyRuleMetadata -> ShowS
$cshowsPrec :: Int -> OrganizationCustomPolicyRuleMetadata -> ShowS
Prelude.Show, forall x.
Rep OrganizationCustomPolicyRuleMetadata x
-> OrganizationCustomPolicyRuleMetadata
forall x.
OrganizationCustomPolicyRuleMetadata
-> Rep OrganizationCustomPolicyRuleMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep OrganizationCustomPolicyRuleMetadata x
-> OrganizationCustomPolicyRuleMetadata
$cfrom :: forall x.
OrganizationCustomPolicyRuleMetadata
-> Rep OrganizationCustomPolicyRuleMetadata x
Prelude.Generic)

-- |
-- Create a value of 'OrganizationCustomPolicyRuleMetadata' 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:
--
-- 'debugLogDeliveryAccounts', 'organizationCustomPolicyRuleMetadata_debugLogDeliveryAccounts' - A list of accounts that you can enable debug logging for your
-- organization Config Custom Policy rule. List is null when debug logging
-- is enabled for all accounts.
--
-- 'description', 'organizationCustomPolicyRuleMetadata_description' - The description that you provide for your organization Config Custom
-- Policy rule.
--
-- 'inputParameters', 'organizationCustomPolicyRuleMetadata_inputParameters' - A string, in JSON format, that is passed to your organization Config
-- Custom Policy rule.
--
-- 'maximumExecutionFrequency', 'organizationCustomPolicyRuleMetadata_maximumExecutionFrequency' - The maximum frequency with which Config runs evaluations for a rule.
-- Your Config Custom Policy rule is triggered when Config delivers the
-- configuration snapshot. For more information, see
-- ConfigSnapshotDeliveryProperties.
--
-- 'organizationConfigRuleTriggerTypes', 'organizationCustomPolicyRuleMetadata_organizationConfigRuleTriggerTypes' - The type of notification that initiates Config to run an evaluation for
-- a rule. For Config Custom Policy rules, Config supports change-initiated
-- notification types:
--
-- -   @ConfigurationItemChangeNotification@ - Initiates an evaluation when
--     Config delivers a configuration item as a result of a resource
--     change.
--
-- -   @OversizedConfigurationItemChangeNotification@ - Initiates an
--     evaluation when Config delivers an oversized configuration item.
--     Config may generate this notification type when a resource changes
--     and the notification exceeds the maximum size allowed by Amazon SNS.
--
-- 'resourceIdScope', 'organizationCustomPolicyRuleMetadata_resourceIdScope' - The ID of the Amazon Web Services resource that was evaluated.
--
-- 'resourceTypesScope', 'organizationCustomPolicyRuleMetadata_resourceTypesScope' - The type of the Amazon Web Services resource that was evaluated.
--
-- 'tagKeyScope', 'organizationCustomPolicyRuleMetadata_tagKeyScope' - One part of a key-value pair that make up a tag. A key is a general
-- label that acts like a category for more specific tag values.
--
-- 'tagValueScope', 'organizationCustomPolicyRuleMetadata_tagValueScope' - The optional part of a key-value pair that make up a tag. A value acts
-- as a descriptor within a tag category (key).
--
-- 'policyRuntime', 'organizationCustomPolicyRuleMetadata_policyRuntime' - The runtime system for your organization Config Custom Policy rules.
-- Guard is a policy-as-code language that allows you to write policies
-- that are enforced by Config Custom Policy rules. For more information
-- about Guard, see the
-- <https://github.com/aws-cloudformation/cloudformation-guard Guard GitHub Repository>.
--
-- 'policyText', 'organizationCustomPolicyRuleMetadata_policyText' - The policy definition containing the logic for your organization Config
-- Custom Policy rule.
newOrganizationCustomPolicyRuleMetadata ::
  -- | 'policyRuntime'
  Prelude.Text ->
  -- | 'policyText'
  Prelude.Text ->
  OrganizationCustomPolicyRuleMetadata
newOrganizationCustomPolicyRuleMetadata :: Text -> Text -> OrganizationCustomPolicyRuleMetadata
newOrganizationCustomPolicyRuleMetadata
  Text
pPolicyRuntime_
  Text
pPolicyText_ =
    OrganizationCustomPolicyRuleMetadata'
      { $sel:debugLogDeliveryAccounts:OrganizationCustomPolicyRuleMetadata' :: Maybe [Text]
debugLogDeliveryAccounts =
          forall a. Maybe a
Prelude.Nothing,
        $sel:description:OrganizationCustomPolicyRuleMetadata' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
        $sel:inputParameters:OrganizationCustomPolicyRuleMetadata' :: Maybe Text
inputParameters = forall a. Maybe a
Prelude.Nothing,
        $sel:maximumExecutionFrequency:OrganizationCustomPolicyRuleMetadata' :: Maybe MaximumExecutionFrequency
maximumExecutionFrequency =
          forall a. Maybe a
Prelude.Nothing,
        $sel:organizationConfigRuleTriggerTypes:OrganizationCustomPolicyRuleMetadata' :: Maybe [OrganizationConfigRuleTriggerTypeNoSN]
organizationConfigRuleTriggerTypes =
          forall a. Maybe a
Prelude.Nothing,
        $sel:resourceIdScope:OrganizationCustomPolicyRuleMetadata' :: Maybe Text
resourceIdScope = forall a. Maybe a
Prelude.Nothing,
        $sel:resourceTypesScope:OrganizationCustomPolicyRuleMetadata' :: Maybe [Text]
resourceTypesScope = forall a. Maybe a
Prelude.Nothing,
        $sel:tagKeyScope:OrganizationCustomPolicyRuleMetadata' :: Maybe Text
tagKeyScope = forall a. Maybe a
Prelude.Nothing,
        $sel:tagValueScope:OrganizationCustomPolicyRuleMetadata' :: Maybe Text
tagValueScope = forall a. Maybe a
Prelude.Nothing,
        $sel:policyRuntime:OrganizationCustomPolicyRuleMetadata' :: Text
policyRuntime = Text
pPolicyRuntime_,
        $sel:policyText:OrganizationCustomPolicyRuleMetadata' :: Text
policyText = Text
pPolicyText_
      }

-- | A list of accounts that you can enable debug logging for your
-- organization Config Custom Policy rule. List is null when debug logging
-- is enabled for all accounts.
organizationCustomPolicyRuleMetadata_debugLogDeliveryAccounts :: Lens.Lens' OrganizationCustomPolicyRuleMetadata (Prelude.Maybe [Prelude.Text])
organizationCustomPolicyRuleMetadata_debugLogDeliveryAccounts :: Lens' OrganizationCustomPolicyRuleMetadata (Maybe [Text])
organizationCustomPolicyRuleMetadata_debugLogDeliveryAccounts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OrganizationCustomPolicyRuleMetadata' {Maybe [Text]
debugLogDeliveryAccounts :: Maybe [Text]
$sel:debugLogDeliveryAccounts:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe [Text]
debugLogDeliveryAccounts} -> Maybe [Text]
debugLogDeliveryAccounts) (\s :: OrganizationCustomPolicyRuleMetadata
s@OrganizationCustomPolicyRuleMetadata' {} Maybe [Text]
a -> OrganizationCustomPolicyRuleMetadata
s {$sel:debugLogDeliveryAccounts:OrganizationCustomPolicyRuleMetadata' :: Maybe [Text]
debugLogDeliveryAccounts = Maybe [Text]
a} :: OrganizationCustomPolicyRuleMetadata) 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 description that you provide for your organization Config Custom
-- Policy rule.
organizationCustomPolicyRuleMetadata_description :: Lens.Lens' OrganizationCustomPolicyRuleMetadata (Prelude.Maybe Prelude.Text)
organizationCustomPolicyRuleMetadata_description :: Lens' OrganizationCustomPolicyRuleMetadata (Maybe Text)
organizationCustomPolicyRuleMetadata_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OrganizationCustomPolicyRuleMetadata' {Maybe Text
description :: Maybe Text
$sel:description:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe Text
description} -> Maybe Text
description) (\s :: OrganizationCustomPolicyRuleMetadata
s@OrganizationCustomPolicyRuleMetadata' {} Maybe Text
a -> OrganizationCustomPolicyRuleMetadata
s {$sel:description:OrganizationCustomPolicyRuleMetadata' :: Maybe Text
description = Maybe Text
a} :: OrganizationCustomPolicyRuleMetadata)

-- | A string, in JSON format, that is passed to your organization Config
-- Custom Policy rule.
organizationCustomPolicyRuleMetadata_inputParameters :: Lens.Lens' OrganizationCustomPolicyRuleMetadata (Prelude.Maybe Prelude.Text)
organizationCustomPolicyRuleMetadata_inputParameters :: Lens' OrganizationCustomPolicyRuleMetadata (Maybe Text)
organizationCustomPolicyRuleMetadata_inputParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OrganizationCustomPolicyRuleMetadata' {Maybe Text
inputParameters :: Maybe Text
$sel:inputParameters:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe Text
inputParameters} -> Maybe Text
inputParameters) (\s :: OrganizationCustomPolicyRuleMetadata
s@OrganizationCustomPolicyRuleMetadata' {} Maybe Text
a -> OrganizationCustomPolicyRuleMetadata
s {$sel:inputParameters:OrganizationCustomPolicyRuleMetadata' :: Maybe Text
inputParameters = Maybe Text
a} :: OrganizationCustomPolicyRuleMetadata)

-- | The maximum frequency with which Config runs evaluations for a rule.
-- Your Config Custom Policy rule is triggered when Config delivers the
-- configuration snapshot. For more information, see
-- ConfigSnapshotDeliveryProperties.
organizationCustomPolicyRuleMetadata_maximumExecutionFrequency :: Lens.Lens' OrganizationCustomPolicyRuleMetadata (Prelude.Maybe MaximumExecutionFrequency)
organizationCustomPolicyRuleMetadata_maximumExecutionFrequency :: Lens'
  OrganizationCustomPolicyRuleMetadata
  (Maybe MaximumExecutionFrequency)
organizationCustomPolicyRuleMetadata_maximumExecutionFrequency = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OrganizationCustomPolicyRuleMetadata' {Maybe MaximumExecutionFrequency
maximumExecutionFrequency :: Maybe MaximumExecutionFrequency
$sel:maximumExecutionFrequency:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata
-> Maybe MaximumExecutionFrequency
maximumExecutionFrequency} -> Maybe MaximumExecutionFrequency
maximumExecutionFrequency) (\s :: OrganizationCustomPolicyRuleMetadata
s@OrganizationCustomPolicyRuleMetadata' {} Maybe MaximumExecutionFrequency
a -> OrganizationCustomPolicyRuleMetadata
s {$sel:maximumExecutionFrequency:OrganizationCustomPolicyRuleMetadata' :: Maybe MaximumExecutionFrequency
maximumExecutionFrequency = Maybe MaximumExecutionFrequency
a} :: OrganizationCustomPolicyRuleMetadata)

-- | The type of notification that initiates Config to run an evaluation for
-- a rule. For Config Custom Policy rules, Config supports change-initiated
-- notification types:
--
-- -   @ConfigurationItemChangeNotification@ - Initiates an evaluation when
--     Config delivers a configuration item as a result of a resource
--     change.
--
-- -   @OversizedConfigurationItemChangeNotification@ - Initiates an
--     evaluation when Config delivers an oversized configuration item.
--     Config may generate this notification type when a resource changes
--     and the notification exceeds the maximum size allowed by Amazon SNS.
organizationCustomPolicyRuleMetadata_organizationConfigRuleTriggerTypes :: Lens.Lens' OrganizationCustomPolicyRuleMetadata (Prelude.Maybe [OrganizationConfigRuleTriggerTypeNoSN])
organizationCustomPolicyRuleMetadata_organizationConfigRuleTriggerTypes :: Lens'
  OrganizationCustomPolicyRuleMetadata
  (Maybe [OrganizationConfigRuleTriggerTypeNoSN])
organizationCustomPolicyRuleMetadata_organizationConfigRuleTriggerTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OrganizationCustomPolicyRuleMetadata' {Maybe [OrganizationConfigRuleTriggerTypeNoSN]
organizationConfigRuleTriggerTypes :: Maybe [OrganizationConfigRuleTriggerTypeNoSN]
$sel:organizationConfigRuleTriggerTypes:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata
-> Maybe [OrganizationConfigRuleTriggerTypeNoSN]
organizationConfigRuleTriggerTypes} -> Maybe [OrganizationConfigRuleTriggerTypeNoSN]
organizationConfigRuleTriggerTypes) (\s :: OrganizationCustomPolicyRuleMetadata
s@OrganizationCustomPolicyRuleMetadata' {} Maybe [OrganizationConfigRuleTriggerTypeNoSN]
a -> OrganizationCustomPolicyRuleMetadata
s {$sel:organizationConfigRuleTriggerTypes:OrganizationCustomPolicyRuleMetadata' :: Maybe [OrganizationConfigRuleTriggerTypeNoSN]
organizationConfigRuleTriggerTypes = Maybe [OrganizationConfigRuleTriggerTypeNoSN]
a} :: OrganizationCustomPolicyRuleMetadata) 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 ID of the Amazon Web Services resource that was evaluated.
organizationCustomPolicyRuleMetadata_resourceIdScope :: Lens.Lens' OrganizationCustomPolicyRuleMetadata (Prelude.Maybe Prelude.Text)
organizationCustomPolicyRuleMetadata_resourceIdScope :: Lens' OrganizationCustomPolicyRuleMetadata (Maybe Text)
organizationCustomPolicyRuleMetadata_resourceIdScope = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OrganizationCustomPolicyRuleMetadata' {Maybe Text
resourceIdScope :: Maybe Text
$sel:resourceIdScope:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe Text
resourceIdScope} -> Maybe Text
resourceIdScope) (\s :: OrganizationCustomPolicyRuleMetadata
s@OrganizationCustomPolicyRuleMetadata' {} Maybe Text
a -> OrganizationCustomPolicyRuleMetadata
s {$sel:resourceIdScope:OrganizationCustomPolicyRuleMetadata' :: Maybe Text
resourceIdScope = Maybe Text
a} :: OrganizationCustomPolicyRuleMetadata)

-- | The type of the Amazon Web Services resource that was evaluated.
organizationCustomPolicyRuleMetadata_resourceTypesScope :: Lens.Lens' OrganizationCustomPolicyRuleMetadata (Prelude.Maybe [Prelude.Text])
organizationCustomPolicyRuleMetadata_resourceTypesScope :: Lens' OrganizationCustomPolicyRuleMetadata (Maybe [Text])
organizationCustomPolicyRuleMetadata_resourceTypesScope = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OrganizationCustomPolicyRuleMetadata' {Maybe [Text]
resourceTypesScope :: Maybe [Text]
$sel:resourceTypesScope:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe [Text]
resourceTypesScope} -> Maybe [Text]
resourceTypesScope) (\s :: OrganizationCustomPolicyRuleMetadata
s@OrganizationCustomPolicyRuleMetadata' {} Maybe [Text]
a -> OrganizationCustomPolicyRuleMetadata
s {$sel:resourceTypesScope:OrganizationCustomPolicyRuleMetadata' :: Maybe [Text]
resourceTypesScope = Maybe [Text]
a} :: OrganizationCustomPolicyRuleMetadata) 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

-- | One part of a key-value pair that make up a tag. A key is a general
-- label that acts like a category for more specific tag values.
organizationCustomPolicyRuleMetadata_tagKeyScope :: Lens.Lens' OrganizationCustomPolicyRuleMetadata (Prelude.Maybe Prelude.Text)
organizationCustomPolicyRuleMetadata_tagKeyScope :: Lens' OrganizationCustomPolicyRuleMetadata (Maybe Text)
organizationCustomPolicyRuleMetadata_tagKeyScope = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OrganizationCustomPolicyRuleMetadata' {Maybe Text
tagKeyScope :: Maybe Text
$sel:tagKeyScope:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe Text
tagKeyScope} -> Maybe Text
tagKeyScope) (\s :: OrganizationCustomPolicyRuleMetadata
s@OrganizationCustomPolicyRuleMetadata' {} Maybe Text
a -> OrganizationCustomPolicyRuleMetadata
s {$sel:tagKeyScope:OrganizationCustomPolicyRuleMetadata' :: Maybe Text
tagKeyScope = Maybe Text
a} :: OrganizationCustomPolicyRuleMetadata)

-- | The optional part of a key-value pair that make up a tag. A value acts
-- as a descriptor within a tag category (key).
organizationCustomPolicyRuleMetadata_tagValueScope :: Lens.Lens' OrganizationCustomPolicyRuleMetadata (Prelude.Maybe Prelude.Text)
organizationCustomPolicyRuleMetadata_tagValueScope :: Lens' OrganizationCustomPolicyRuleMetadata (Maybe Text)
organizationCustomPolicyRuleMetadata_tagValueScope = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OrganizationCustomPolicyRuleMetadata' {Maybe Text
tagValueScope :: Maybe Text
$sel:tagValueScope:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe Text
tagValueScope} -> Maybe Text
tagValueScope) (\s :: OrganizationCustomPolicyRuleMetadata
s@OrganizationCustomPolicyRuleMetadata' {} Maybe Text
a -> OrganizationCustomPolicyRuleMetadata
s {$sel:tagValueScope:OrganizationCustomPolicyRuleMetadata' :: Maybe Text
tagValueScope = Maybe Text
a} :: OrganizationCustomPolicyRuleMetadata)

-- | The runtime system for your organization Config Custom Policy rules.
-- Guard is a policy-as-code language that allows you to write policies
-- that are enforced by Config Custom Policy rules. For more information
-- about Guard, see the
-- <https://github.com/aws-cloudformation/cloudformation-guard Guard GitHub Repository>.
organizationCustomPolicyRuleMetadata_policyRuntime :: Lens.Lens' OrganizationCustomPolicyRuleMetadata Prelude.Text
organizationCustomPolicyRuleMetadata_policyRuntime :: Lens' OrganizationCustomPolicyRuleMetadata Text
organizationCustomPolicyRuleMetadata_policyRuntime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OrganizationCustomPolicyRuleMetadata' {Text
policyRuntime :: Text
$sel:policyRuntime:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Text
policyRuntime} -> Text
policyRuntime) (\s :: OrganizationCustomPolicyRuleMetadata
s@OrganizationCustomPolicyRuleMetadata' {} Text
a -> OrganizationCustomPolicyRuleMetadata
s {$sel:policyRuntime:OrganizationCustomPolicyRuleMetadata' :: Text
policyRuntime = Text
a} :: OrganizationCustomPolicyRuleMetadata)

-- | The policy definition containing the logic for your organization Config
-- Custom Policy rule.
organizationCustomPolicyRuleMetadata_policyText :: Lens.Lens' OrganizationCustomPolicyRuleMetadata Prelude.Text
organizationCustomPolicyRuleMetadata_policyText :: Lens' OrganizationCustomPolicyRuleMetadata Text
organizationCustomPolicyRuleMetadata_policyText = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OrganizationCustomPolicyRuleMetadata' {Text
policyText :: Text
$sel:policyText:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Text
policyText} -> Text
policyText) (\s :: OrganizationCustomPolicyRuleMetadata
s@OrganizationCustomPolicyRuleMetadata' {} Text
a -> OrganizationCustomPolicyRuleMetadata
s {$sel:policyText:OrganizationCustomPolicyRuleMetadata' :: Text
policyText = Text
a} :: OrganizationCustomPolicyRuleMetadata)

instance
  Prelude.Hashable
    OrganizationCustomPolicyRuleMetadata
  where
  hashWithSalt :: Int -> OrganizationCustomPolicyRuleMetadata -> Int
hashWithSalt
    Int
_salt
    OrganizationCustomPolicyRuleMetadata' {Maybe [Text]
Maybe [OrganizationConfigRuleTriggerTypeNoSN]
Maybe Text
Maybe MaximumExecutionFrequency
Text
policyText :: Text
policyRuntime :: Text
tagValueScope :: Maybe Text
tagKeyScope :: Maybe Text
resourceTypesScope :: Maybe [Text]
resourceIdScope :: Maybe Text
organizationConfigRuleTriggerTypes :: Maybe [OrganizationConfigRuleTriggerTypeNoSN]
maximumExecutionFrequency :: Maybe MaximumExecutionFrequency
inputParameters :: Maybe Text
description :: Maybe Text
debugLogDeliveryAccounts :: Maybe [Text]
$sel:policyText:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Text
$sel:policyRuntime:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Text
$sel:tagValueScope:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe Text
$sel:tagKeyScope:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe Text
$sel:resourceTypesScope:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe [Text]
$sel:resourceIdScope:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe Text
$sel:organizationConfigRuleTriggerTypes:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata
-> Maybe [OrganizationConfigRuleTriggerTypeNoSN]
$sel:maximumExecutionFrequency:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata
-> Maybe MaximumExecutionFrequency
$sel:inputParameters:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe Text
$sel:description:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe Text
$sel:debugLogDeliveryAccounts:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe [Text]
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
debugLogDeliveryAccounts
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
inputParameters
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MaximumExecutionFrequency
maximumExecutionFrequency
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [OrganizationConfigRuleTriggerTypeNoSN]
organizationConfigRuleTriggerTypes
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceIdScope
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
resourceTypesScope
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
tagKeyScope
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
tagValueScope
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policyRuntime
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policyText

instance
  Prelude.NFData
    OrganizationCustomPolicyRuleMetadata
  where
  rnf :: OrganizationCustomPolicyRuleMetadata -> ()
rnf OrganizationCustomPolicyRuleMetadata' {Maybe [Text]
Maybe [OrganizationConfigRuleTriggerTypeNoSN]
Maybe Text
Maybe MaximumExecutionFrequency
Text
policyText :: Text
policyRuntime :: Text
tagValueScope :: Maybe Text
tagKeyScope :: Maybe Text
resourceTypesScope :: Maybe [Text]
resourceIdScope :: Maybe Text
organizationConfigRuleTriggerTypes :: Maybe [OrganizationConfigRuleTriggerTypeNoSN]
maximumExecutionFrequency :: Maybe MaximumExecutionFrequency
inputParameters :: Maybe Text
description :: Maybe Text
debugLogDeliveryAccounts :: Maybe [Text]
$sel:policyText:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Text
$sel:policyRuntime:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Text
$sel:tagValueScope:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe Text
$sel:tagKeyScope:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe Text
$sel:resourceTypesScope:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe [Text]
$sel:resourceIdScope:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe Text
$sel:organizationConfigRuleTriggerTypes:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata
-> Maybe [OrganizationConfigRuleTriggerTypeNoSN]
$sel:maximumExecutionFrequency:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata
-> Maybe MaximumExecutionFrequency
$sel:inputParameters:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe Text
$sel:description:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe Text
$sel:debugLogDeliveryAccounts:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
debugLogDeliveryAccounts
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
inputParameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MaximumExecutionFrequency
maximumExecutionFrequency
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [OrganizationConfigRuleTriggerTypeNoSN]
organizationConfigRuleTriggerTypes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
resourceIdScope
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
resourceTypesScope
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
tagKeyScope
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
tagValueScope
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
policyRuntime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
policyText

instance
  Data.ToJSON
    OrganizationCustomPolicyRuleMetadata
  where
  toJSON :: OrganizationCustomPolicyRuleMetadata -> Value
toJSON OrganizationCustomPolicyRuleMetadata' {Maybe [Text]
Maybe [OrganizationConfigRuleTriggerTypeNoSN]
Maybe Text
Maybe MaximumExecutionFrequency
Text
policyText :: Text
policyRuntime :: Text
tagValueScope :: Maybe Text
tagKeyScope :: Maybe Text
resourceTypesScope :: Maybe [Text]
resourceIdScope :: Maybe Text
organizationConfigRuleTriggerTypes :: Maybe [OrganizationConfigRuleTriggerTypeNoSN]
maximumExecutionFrequency :: Maybe MaximumExecutionFrequency
inputParameters :: Maybe Text
description :: Maybe Text
debugLogDeliveryAccounts :: Maybe [Text]
$sel:policyText:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Text
$sel:policyRuntime:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Text
$sel:tagValueScope:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe Text
$sel:tagKeyScope:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe Text
$sel:resourceTypesScope:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe [Text]
$sel:resourceIdScope:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe Text
$sel:organizationConfigRuleTriggerTypes:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata
-> Maybe [OrganizationConfigRuleTriggerTypeNoSN]
$sel:maximumExecutionFrequency:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata
-> Maybe MaximumExecutionFrequency
$sel:inputParameters:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe Text
$sel:description:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe Text
$sel:debugLogDeliveryAccounts:OrganizationCustomPolicyRuleMetadata' :: OrganizationCustomPolicyRuleMetadata -> Maybe [Text]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"DebugLogDeliveryAccounts" 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]
debugLogDeliveryAccounts,
            (Key
"Description" 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
description,
            (Key
"InputParameters" 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
inputParameters,
            (Key
"MaximumExecutionFrequency" 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 MaximumExecutionFrequency
maximumExecutionFrequency,
            (Key
"OrganizationConfigRuleTriggerTypes" 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 [OrganizationConfigRuleTriggerTypeNoSN]
organizationConfigRuleTriggerTypes,
            (Key
"ResourceIdScope" 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
resourceIdScope,
            (Key
"ResourceTypesScope" 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]
resourceTypesScope,
            (Key
"TagKeyScope" 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
tagKeyScope,
            (Key
"TagValueScope" 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
tagValueScope,
            forall a. a -> Maybe a
Prelude.Just (Key
"PolicyRuntime" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
policyRuntime),
            forall a. a -> Maybe a
Prelude.Just (Key
"PolicyText" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
policyText)
          ]
      )