{-# 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.AuditManager.Types.SourceKeyword
-- 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.AuditManager.Types.SourceKeyword where

import Amazonka.AuditManager.Types.KeywordInputType
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

-- | The keyword to search for in CloudTrail logs, Config rules, Security Hub
-- checks, and Amazon Web Services API names.
--
-- To learn more about the supported keywords that you can use when mapping
-- a control data source, see the following pages in the /Audit Manager
-- User Guide/:
--
-- -   <https://docs.aws.amazon.com/audit-manager/latest/userguide/control-data-sources-ash.html Config rules supported by Audit Manager>
--
-- -   <https://docs.aws.amazon.com/audit-manager/latest/userguide/control-data-sources-config.html Security Hub controls supported by Audit Manager>
--
-- -   <https://docs.aws.amazon.com/audit-manager/latest/userguide/control-data-sources-api.html API calls supported by Audit Manager>
--
-- -   <https://docs.aws.amazon.com/audit-manager/latest/userguide/control-data-sources-cloudtrail.html CloudTrail event names supported by Audit Manager>
--
-- /See:/ 'newSourceKeyword' smart constructor.
data SourceKeyword = SourceKeyword'
  { -- | The input method for the keyword.
    SourceKeyword -> Maybe KeywordInputType
keywordInputType :: Prelude.Maybe KeywordInputType,
    -- | The value of the keyword that\'s used when mapping a control data
    -- source. For example, this can be a CloudTrail event name, a rule name
    -- for Config, a Security Hub control, or the name of an Amazon Web
    -- Services API call.
    --
    -- If you’re mapping a data source to a rule in Config, the @keywordValue@
    -- that you specify depends on the type of rule:
    --
    -- -   For
    --     <https://docs.aws.amazon.com/config/latest/developerguide/evaluate-config_use-managed-rules.html managed rules>,
    --     you can use the rule identifier as the @keywordValue@. You can find
    --     the rule identifier from the
    --     <https://docs.aws.amazon.com/config/latest/developerguide/managed-rules-by-aws-config.html list of Config managed rules>.
    --
    --     -   Managed rule name:
    --         <https://docs.aws.amazon.com/config/latest/developerguide/s3-bucket-acl-prohibited.html s3-bucket-acl-prohibited>
    --
    --         @keywordValue@: @S3_BUCKET_ACL_PROHIBITED@
    --
    -- -   For
    --     <https://docs.aws.amazon.com/config/latest/developerguide/evaluate-config_develop-rules.html custom rules>,
    --     you form the @keywordValue@ by adding the @Custom_@ prefix to the
    --     rule name. This prefix distinguishes the rule from a managed rule.
    --
    --     -   Custom rule name: my-custom-config-rule
    --
    --         @keywordValue@: @Custom_my-custom-config-rule@
    --
    -- -   For
    --     <https://docs.aws.amazon.com/config/latest/developerguide/service-linked-awsconfig-rules.html service-linked rules>,
    --     you form the @keywordValue@ by adding the @Custom_@ prefix to the
    --     rule name. In addition, you remove the suffix ID that appears at the
    --     end of the rule name.
    --
    --     -   Service-linked rule name:
    --         CustomRuleForAccount-conformance-pack-szsm1uv0w
    --
    --         @keywordValue@: @Custom_CustomRuleForAccount-conformance-pack@
    --
    --     -   Service-linked rule name:
    --         OrgConfigRule-s3-bucket-versioning-enabled-dbgzf8ba
    --
    --         @keywordValue@:
    --         @Custom_OrgConfigRule-s3-bucket-versioning-enabled@
    SourceKeyword -> Maybe Text
keywordValue :: Prelude.Maybe Prelude.Text
  }
  deriving (SourceKeyword -> SourceKeyword -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SourceKeyword -> SourceKeyword -> Bool
$c/= :: SourceKeyword -> SourceKeyword -> Bool
== :: SourceKeyword -> SourceKeyword -> Bool
$c== :: SourceKeyword -> SourceKeyword -> Bool
Prelude.Eq, ReadPrec [SourceKeyword]
ReadPrec SourceKeyword
Int -> ReadS SourceKeyword
ReadS [SourceKeyword]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SourceKeyword]
$creadListPrec :: ReadPrec [SourceKeyword]
readPrec :: ReadPrec SourceKeyword
$creadPrec :: ReadPrec SourceKeyword
readList :: ReadS [SourceKeyword]
$creadList :: ReadS [SourceKeyword]
readsPrec :: Int -> ReadS SourceKeyword
$creadsPrec :: Int -> ReadS SourceKeyword
Prelude.Read, Int -> SourceKeyword -> ShowS
[SourceKeyword] -> ShowS
SourceKeyword -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SourceKeyword] -> ShowS
$cshowList :: [SourceKeyword] -> ShowS
show :: SourceKeyword -> String
$cshow :: SourceKeyword -> String
showsPrec :: Int -> SourceKeyword -> ShowS
$cshowsPrec :: Int -> SourceKeyword -> ShowS
Prelude.Show, forall x. Rep SourceKeyword x -> SourceKeyword
forall x. SourceKeyword -> Rep SourceKeyword x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SourceKeyword x -> SourceKeyword
$cfrom :: forall x. SourceKeyword -> Rep SourceKeyword x
Prelude.Generic)

-- |
-- Create a value of 'SourceKeyword' 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:
--
-- 'keywordInputType', 'sourceKeyword_keywordInputType' - The input method for the keyword.
--
-- 'keywordValue', 'sourceKeyword_keywordValue' - The value of the keyword that\'s used when mapping a control data
-- source. For example, this can be a CloudTrail event name, a rule name
-- for Config, a Security Hub control, or the name of an Amazon Web
-- Services API call.
--
-- If you’re mapping a data source to a rule in Config, the @keywordValue@
-- that you specify depends on the type of rule:
--
-- -   For
--     <https://docs.aws.amazon.com/config/latest/developerguide/evaluate-config_use-managed-rules.html managed rules>,
--     you can use the rule identifier as the @keywordValue@. You can find
--     the rule identifier from the
--     <https://docs.aws.amazon.com/config/latest/developerguide/managed-rules-by-aws-config.html list of Config managed rules>.
--
--     -   Managed rule name:
--         <https://docs.aws.amazon.com/config/latest/developerguide/s3-bucket-acl-prohibited.html s3-bucket-acl-prohibited>
--
--         @keywordValue@: @S3_BUCKET_ACL_PROHIBITED@
--
-- -   For
--     <https://docs.aws.amazon.com/config/latest/developerguide/evaluate-config_develop-rules.html custom rules>,
--     you form the @keywordValue@ by adding the @Custom_@ prefix to the
--     rule name. This prefix distinguishes the rule from a managed rule.
--
--     -   Custom rule name: my-custom-config-rule
--
--         @keywordValue@: @Custom_my-custom-config-rule@
--
-- -   For
--     <https://docs.aws.amazon.com/config/latest/developerguide/service-linked-awsconfig-rules.html service-linked rules>,
--     you form the @keywordValue@ by adding the @Custom_@ prefix to the
--     rule name. In addition, you remove the suffix ID that appears at the
--     end of the rule name.
--
--     -   Service-linked rule name:
--         CustomRuleForAccount-conformance-pack-szsm1uv0w
--
--         @keywordValue@: @Custom_CustomRuleForAccount-conformance-pack@
--
--     -   Service-linked rule name:
--         OrgConfigRule-s3-bucket-versioning-enabled-dbgzf8ba
--
--         @keywordValue@:
--         @Custom_OrgConfigRule-s3-bucket-versioning-enabled@
newSourceKeyword ::
  SourceKeyword
newSourceKeyword :: SourceKeyword
newSourceKeyword =
  SourceKeyword'
    { $sel:keywordInputType:SourceKeyword' :: Maybe KeywordInputType
keywordInputType = forall a. Maybe a
Prelude.Nothing,
      $sel:keywordValue:SourceKeyword' :: Maybe Text
keywordValue = forall a. Maybe a
Prelude.Nothing
    }

-- | The input method for the keyword.
sourceKeyword_keywordInputType :: Lens.Lens' SourceKeyword (Prelude.Maybe KeywordInputType)
sourceKeyword_keywordInputType :: Lens' SourceKeyword (Maybe KeywordInputType)
sourceKeyword_keywordInputType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SourceKeyword' {Maybe KeywordInputType
keywordInputType :: Maybe KeywordInputType
$sel:keywordInputType:SourceKeyword' :: SourceKeyword -> Maybe KeywordInputType
keywordInputType} -> Maybe KeywordInputType
keywordInputType) (\s :: SourceKeyword
s@SourceKeyword' {} Maybe KeywordInputType
a -> SourceKeyword
s {$sel:keywordInputType:SourceKeyword' :: Maybe KeywordInputType
keywordInputType = Maybe KeywordInputType
a} :: SourceKeyword)

-- | The value of the keyword that\'s used when mapping a control data
-- source. For example, this can be a CloudTrail event name, a rule name
-- for Config, a Security Hub control, or the name of an Amazon Web
-- Services API call.
--
-- If you’re mapping a data source to a rule in Config, the @keywordValue@
-- that you specify depends on the type of rule:
--
-- -   For
--     <https://docs.aws.amazon.com/config/latest/developerguide/evaluate-config_use-managed-rules.html managed rules>,
--     you can use the rule identifier as the @keywordValue@. You can find
--     the rule identifier from the
--     <https://docs.aws.amazon.com/config/latest/developerguide/managed-rules-by-aws-config.html list of Config managed rules>.
--
--     -   Managed rule name:
--         <https://docs.aws.amazon.com/config/latest/developerguide/s3-bucket-acl-prohibited.html s3-bucket-acl-prohibited>
--
--         @keywordValue@: @S3_BUCKET_ACL_PROHIBITED@
--
-- -   For
--     <https://docs.aws.amazon.com/config/latest/developerguide/evaluate-config_develop-rules.html custom rules>,
--     you form the @keywordValue@ by adding the @Custom_@ prefix to the
--     rule name. This prefix distinguishes the rule from a managed rule.
--
--     -   Custom rule name: my-custom-config-rule
--
--         @keywordValue@: @Custom_my-custom-config-rule@
--
-- -   For
--     <https://docs.aws.amazon.com/config/latest/developerguide/service-linked-awsconfig-rules.html service-linked rules>,
--     you form the @keywordValue@ by adding the @Custom_@ prefix to the
--     rule name. In addition, you remove the suffix ID that appears at the
--     end of the rule name.
--
--     -   Service-linked rule name:
--         CustomRuleForAccount-conformance-pack-szsm1uv0w
--
--         @keywordValue@: @Custom_CustomRuleForAccount-conformance-pack@
--
--     -   Service-linked rule name:
--         OrgConfigRule-s3-bucket-versioning-enabled-dbgzf8ba
--
--         @keywordValue@:
--         @Custom_OrgConfigRule-s3-bucket-versioning-enabled@
sourceKeyword_keywordValue :: Lens.Lens' SourceKeyword (Prelude.Maybe Prelude.Text)
sourceKeyword_keywordValue :: Lens' SourceKeyword (Maybe Text)
sourceKeyword_keywordValue = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SourceKeyword' {Maybe Text
keywordValue :: Maybe Text
$sel:keywordValue:SourceKeyword' :: SourceKeyword -> Maybe Text
keywordValue} -> Maybe Text
keywordValue) (\s :: SourceKeyword
s@SourceKeyword' {} Maybe Text
a -> SourceKeyword
s {$sel:keywordValue:SourceKeyword' :: Maybe Text
keywordValue = Maybe Text
a} :: SourceKeyword)

instance Data.FromJSON SourceKeyword where
  parseJSON :: Value -> Parser SourceKeyword
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"SourceKeyword"
      ( \Object
x ->
          Maybe KeywordInputType -> Maybe Text -> SourceKeyword
SourceKeyword'
            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
"keywordInputType")
            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
"keywordValue")
      )

instance Prelude.Hashable SourceKeyword where
  hashWithSalt :: Int -> SourceKeyword -> Int
hashWithSalt Int
_salt SourceKeyword' {Maybe Text
Maybe KeywordInputType
keywordValue :: Maybe Text
keywordInputType :: Maybe KeywordInputType
$sel:keywordValue:SourceKeyword' :: SourceKeyword -> Maybe Text
$sel:keywordInputType:SourceKeyword' :: SourceKeyword -> Maybe KeywordInputType
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe KeywordInputType
keywordInputType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
keywordValue

instance Prelude.NFData SourceKeyword where
  rnf :: SourceKeyword -> ()
rnf SourceKeyword' {Maybe Text
Maybe KeywordInputType
keywordValue :: Maybe Text
keywordInputType :: Maybe KeywordInputType
$sel:keywordValue:SourceKeyword' :: SourceKeyword -> Maybe Text
$sel:keywordInputType:SourceKeyword' :: SourceKeyword -> Maybe KeywordInputType
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe KeywordInputType
keywordInputType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
keywordValue

instance Data.ToJSON SourceKeyword where
  toJSON :: SourceKeyword -> Value
toJSON SourceKeyword' {Maybe Text
Maybe KeywordInputType
keywordValue :: Maybe Text
keywordInputType :: Maybe KeywordInputType
$sel:keywordValue:SourceKeyword' :: SourceKeyword -> Maybe Text
$sel:keywordInputType:SourceKeyword' :: SourceKeyword -> Maybe KeywordInputType
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"keywordInputType" 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 KeywordInputType
keywordInputType,
            (Key
"keywordValue" 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
keywordValue
          ]
      )