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

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

-- |
-- Module      : Amazonka.MacieV2.GetCustomDataIdentifier
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves the criteria and other settings for a custom data identifier.
module Amazonka.MacieV2.GetCustomDataIdentifier
  ( -- * Creating a Request
    GetCustomDataIdentifier (..),
    newGetCustomDataIdentifier,

    -- * Request Lenses
    getCustomDataIdentifier_id,

    -- * Destructuring the Response
    GetCustomDataIdentifierResponse (..),
    newGetCustomDataIdentifierResponse,

    -- * Response Lenses
    getCustomDataIdentifierResponse_arn,
    getCustomDataIdentifierResponse_createdAt,
    getCustomDataIdentifierResponse_deleted,
    getCustomDataIdentifierResponse_description,
    getCustomDataIdentifierResponse_id,
    getCustomDataIdentifierResponse_ignoreWords,
    getCustomDataIdentifierResponse_keywords,
    getCustomDataIdentifierResponse_maximumMatchDistance,
    getCustomDataIdentifierResponse_name,
    getCustomDataIdentifierResponse_regex,
    getCustomDataIdentifierResponse_severityLevels,
    getCustomDataIdentifierResponse_tags,
    getCustomDataIdentifierResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetCustomDataIdentifier' smart constructor.
data GetCustomDataIdentifier = GetCustomDataIdentifier'
  { -- | The unique identifier for the Amazon Macie resource that the request
    -- applies to.
    GetCustomDataIdentifier -> Text
id :: Prelude.Text
  }
  deriving (GetCustomDataIdentifier -> GetCustomDataIdentifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCustomDataIdentifier -> GetCustomDataIdentifier -> Bool
$c/= :: GetCustomDataIdentifier -> GetCustomDataIdentifier -> Bool
== :: GetCustomDataIdentifier -> GetCustomDataIdentifier -> Bool
$c== :: GetCustomDataIdentifier -> GetCustomDataIdentifier -> Bool
Prelude.Eq, ReadPrec [GetCustomDataIdentifier]
ReadPrec GetCustomDataIdentifier
Int -> ReadS GetCustomDataIdentifier
ReadS [GetCustomDataIdentifier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCustomDataIdentifier]
$creadListPrec :: ReadPrec [GetCustomDataIdentifier]
readPrec :: ReadPrec GetCustomDataIdentifier
$creadPrec :: ReadPrec GetCustomDataIdentifier
readList :: ReadS [GetCustomDataIdentifier]
$creadList :: ReadS [GetCustomDataIdentifier]
readsPrec :: Int -> ReadS GetCustomDataIdentifier
$creadsPrec :: Int -> ReadS GetCustomDataIdentifier
Prelude.Read, Int -> GetCustomDataIdentifier -> ShowS
[GetCustomDataIdentifier] -> ShowS
GetCustomDataIdentifier -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCustomDataIdentifier] -> ShowS
$cshowList :: [GetCustomDataIdentifier] -> ShowS
show :: GetCustomDataIdentifier -> String
$cshow :: GetCustomDataIdentifier -> String
showsPrec :: Int -> GetCustomDataIdentifier -> ShowS
$cshowsPrec :: Int -> GetCustomDataIdentifier -> ShowS
Prelude.Show, forall x. Rep GetCustomDataIdentifier x -> GetCustomDataIdentifier
forall x. GetCustomDataIdentifier -> Rep GetCustomDataIdentifier x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCustomDataIdentifier x -> GetCustomDataIdentifier
$cfrom :: forall x. GetCustomDataIdentifier -> Rep GetCustomDataIdentifier x
Prelude.Generic)

-- |
-- Create a value of 'GetCustomDataIdentifier' 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:
--
-- 'id', 'getCustomDataIdentifier_id' - The unique identifier for the Amazon Macie resource that the request
-- applies to.
newGetCustomDataIdentifier ::
  -- | 'id'
  Prelude.Text ->
  GetCustomDataIdentifier
newGetCustomDataIdentifier :: Text -> GetCustomDataIdentifier
newGetCustomDataIdentifier Text
pId_ =
  GetCustomDataIdentifier' {$sel:id:GetCustomDataIdentifier' :: Text
id = Text
pId_}

-- | The unique identifier for the Amazon Macie resource that the request
-- applies to.
getCustomDataIdentifier_id :: Lens.Lens' GetCustomDataIdentifier Prelude.Text
getCustomDataIdentifier_id :: Lens' GetCustomDataIdentifier Text
getCustomDataIdentifier_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCustomDataIdentifier' {Text
id :: Text
$sel:id:GetCustomDataIdentifier' :: GetCustomDataIdentifier -> Text
id} -> Text
id) (\s :: GetCustomDataIdentifier
s@GetCustomDataIdentifier' {} Text
a -> GetCustomDataIdentifier
s {$sel:id:GetCustomDataIdentifier' :: Text
id = Text
a} :: GetCustomDataIdentifier)

instance Core.AWSRequest GetCustomDataIdentifier where
  type
    AWSResponse GetCustomDataIdentifier =
      GetCustomDataIdentifierResponse
  request :: (Service -> Service)
-> GetCustomDataIdentifier -> Request GetCustomDataIdentifier
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetCustomDataIdentifier
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetCustomDataIdentifier)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Maybe ISO8601
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe [SeverityLevel]
-> Maybe (HashMap Text Text)
-> Int
-> GetCustomDataIdentifierResponse
GetCustomDataIdentifierResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"arn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"createdAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"deleted")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (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 -> Either String (Maybe 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 -> Either String (Maybe a)
Data..?> Key
"ignoreWords" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ 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 -> Either String (Maybe a)
Data..?> Key
"keywords" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ 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 -> Either String (Maybe a)
Data..?> Key
"maximumMatchDistance")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (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 -> Either String (Maybe a)
Data..?> Key
"regex")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"severityLevels" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ 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 -> Either String (Maybe a)
Data..?> Key
"tags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable GetCustomDataIdentifier where
  hashWithSalt :: Int -> GetCustomDataIdentifier -> Int
hashWithSalt Int
_salt GetCustomDataIdentifier' {Text
id :: Text
$sel:id:GetCustomDataIdentifier' :: GetCustomDataIdentifier -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

instance Prelude.NFData GetCustomDataIdentifier where
  rnf :: GetCustomDataIdentifier -> ()
rnf GetCustomDataIdentifier' {Text
id :: Text
$sel:id:GetCustomDataIdentifier' :: GetCustomDataIdentifier -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
id

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

instance Data.ToPath GetCustomDataIdentifier where
  toPath :: GetCustomDataIdentifier -> ByteString
toPath GetCustomDataIdentifier' {Text
id :: Text
$sel:id:GetCustomDataIdentifier' :: GetCustomDataIdentifier -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/custom-data-identifiers/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
id]

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

-- | /See:/ 'newGetCustomDataIdentifierResponse' smart constructor.
data GetCustomDataIdentifierResponse = GetCustomDataIdentifierResponse'
  { -- | The Amazon Resource Name (ARN) of the custom data identifier.
    GetCustomDataIdentifierResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The date and time, in UTC and extended ISO 8601 format, when the custom
    -- data identifier was created.
    GetCustomDataIdentifierResponse -> Maybe ISO8601
createdAt :: Prelude.Maybe Data.ISO8601,
    -- | Specifies whether the custom data identifier was deleted. If you delete
    -- a custom data identifier, Amazon Macie doesn\'t delete it permanently.
    -- Instead, it soft deletes the identifier.
    GetCustomDataIdentifierResponse -> Maybe Bool
deleted :: Prelude.Maybe Prelude.Bool,
    -- | The custom description of the custom data identifier.
    GetCustomDataIdentifierResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier for the custom data identifier.
    GetCustomDataIdentifierResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | An array that lists specific character sequences (/ignore words/) to
    -- exclude from the results. If the text matched by the regular expression
    -- contains any string in this array, Amazon Macie ignores it. Ignore words
    -- are case sensitive.
    GetCustomDataIdentifierResponse -> Maybe [Text]
ignoreWords :: Prelude.Maybe [Prelude.Text],
    -- | An array that lists specific character sequences (/keywords/), one of
    -- which must precede and be within proximity (maximumMatchDistance) of the
    -- regular expression to match. Keywords aren\'t case sensitive.
    GetCustomDataIdentifierResponse -> Maybe [Text]
keywords :: Prelude.Maybe [Prelude.Text],
    -- | The maximum number of characters that can exist between the end of at
    -- least one complete character sequence specified by the keywords array
    -- and the end of the text that matches the regex pattern. If a complete
    -- keyword precedes all the text that matches the pattern and the keyword
    -- is within the specified distance, Amazon Macie includes the result.
    -- Otherwise, Macie excludes the result.
    GetCustomDataIdentifierResponse -> Maybe Int
maximumMatchDistance :: Prelude.Maybe Prelude.Int,
    -- | The custom name of the custom data identifier.
    GetCustomDataIdentifierResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The regular expression (/regex/) that defines the pattern to match.
    GetCustomDataIdentifierResponse -> Maybe Text
regex :: Prelude.Maybe Prelude.Text,
    -- | Specifies the severity that\'s assigned to findings that the custom data
    -- identifier produces, based on the number of occurrences of text that
    -- matches the custom data identifier\'s detection criteria. By default,
    -- Amazon Macie creates findings for S3 objects that contain at least one
    -- occurrence of text that matches the detection criteria, and Macie
    -- assigns the MEDIUM severity to those findings.
    GetCustomDataIdentifierResponse -> Maybe [SeverityLevel]
severityLevels :: Prelude.Maybe [SeverityLevel],
    -- | A map of key-value pairs that identifies the tags (keys and values) that
    -- are associated with the custom data identifier.
    GetCustomDataIdentifierResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The response's http status code.
    GetCustomDataIdentifierResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetCustomDataIdentifierResponse
-> GetCustomDataIdentifierResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCustomDataIdentifierResponse
-> GetCustomDataIdentifierResponse -> Bool
$c/= :: GetCustomDataIdentifierResponse
-> GetCustomDataIdentifierResponse -> Bool
== :: GetCustomDataIdentifierResponse
-> GetCustomDataIdentifierResponse -> Bool
$c== :: GetCustomDataIdentifierResponse
-> GetCustomDataIdentifierResponse -> Bool
Prelude.Eq, ReadPrec [GetCustomDataIdentifierResponse]
ReadPrec GetCustomDataIdentifierResponse
Int -> ReadS GetCustomDataIdentifierResponse
ReadS [GetCustomDataIdentifierResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCustomDataIdentifierResponse]
$creadListPrec :: ReadPrec [GetCustomDataIdentifierResponse]
readPrec :: ReadPrec GetCustomDataIdentifierResponse
$creadPrec :: ReadPrec GetCustomDataIdentifierResponse
readList :: ReadS [GetCustomDataIdentifierResponse]
$creadList :: ReadS [GetCustomDataIdentifierResponse]
readsPrec :: Int -> ReadS GetCustomDataIdentifierResponse
$creadsPrec :: Int -> ReadS GetCustomDataIdentifierResponse
Prelude.Read, Int -> GetCustomDataIdentifierResponse -> ShowS
[GetCustomDataIdentifierResponse] -> ShowS
GetCustomDataIdentifierResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCustomDataIdentifierResponse] -> ShowS
$cshowList :: [GetCustomDataIdentifierResponse] -> ShowS
show :: GetCustomDataIdentifierResponse -> String
$cshow :: GetCustomDataIdentifierResponse -> String
showsPrec :: Int -> GetCustomDataIdentifierResponse -> ShowS
$cshowsPrec :: Int -> GetCustomDataIdentifierResponse -> ShowS
Prelude.Show, forall x.
Rep GetCustomDataIdentifierResponse x
-> GetCustomDataIdentifierResponse
forall x.
GetCustomDataIdentifierResponse
-> Rep GetCustomDataIdentifierResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetCustomDataIdentifierResponse x
-> GetCustomDataIdentifierResponse
$cfrom :: forall x.
GetCustomDataIdentifierResponse
-> Rep GetCustomDataIdentifierResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetCustomDataIdentifierResponse' 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:
--
-- 'arn', 'getCustomDataIdentifierResponse_arn' - The Amazon Resource Name (ARN) of the custom data identifier.
--
-- 'createdAt', 'getCustomDataIdentifierResponse_createdAt' - The date and time, in UTC and extended ISO 8601 format, when the custom
-- data identifier was created.
--
-- 'deleted', 'getCustomDataIdentifierResponse_deleted' - Specifies whether the custom data identifier was deleted. If you delete
-- a custom data identifier, Amazon Macie doesn\'t delete it permanently.
-- Instead, it soft deletes the identifier.
--
-- 'description', 'getCustomDataIdentifierResponse_description' - The custom description of the custom data identifier.
--
-- 'id', 'getCustomDataIdentifierResponse_id' - The unique identifier for the custom data identifier.
--
-- 'ignoreWords', 'getCustomDataIdentifierResponse_ignoreWords' - An array that lists specific character sequences (/ignore words/) to
-- exclude from the results. If the text matched by the regular expression
-- contains any string in this array, Amazon Macie ignores it. Ignore words
-- are case sensitive.
--
-- 'keywords', 'getCustomDataIdentifierResponse_keywords' - An array that lists specific character sequences (/keywords/), one of
-- which must precede and be within proximity (maximumMatchDistance) of the
-- regular expression to match. Keywords aren\'t case sensitive.
--
-- 'maximumMatchDistance', 'getCustomDataIdentifierResponse_maximumMatchDistance' - The maximum number of characters that can exist between the end of at
-- least one complete character sequence specified by the keywords array
-- and the end of the text that matches the regex pattern. If a complete
-- keyword precedes all the text that matches the pattern and the keyword
-- is within the specified distance, Amazon Macie includes the result.
-- Otherwise, Macie excludes the result.
--
-- 'name', 'getCustomDataIdentifierResponse_name' - The custom name of the custom data identifier.
--
-- 'regex', 'getCustomDataIdentifierResponse_regex' - The regular expression (/regex/) that defines the pattern to match.
--
-- 'severityLevels', 'getCustomDataIdentifierResponse_severityLevels' - Specifies the severity that\'s assigned to findings that the custom data
-- identifier produces, based on the number of occurrences of text that
-- matches the custom data identifier\'s detection criteria. By default,
-- Amazon Macie creates findings for S3 objects that contain at least one
-- occurrence of text that matches the detection criteria, and Macie
-- assigns the MEDIUM severity to those findings.
--
-- 'tags', 'getCustomDataIdentifierResponse_tags' - A map of key-value pairs that identifies the tags (keys and values) that
-- are associated with the custom data identifier.
--
-- 'httpStatus', 'getCustomDataIdentifierResponse_httpStatus' - The response's http status code.
newGetCustomDataIdentifierResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetCustomDataIdentifierResponse
newGetCustomDataIdentifierResponse :: Int -> GetCustomDataIdentifierResponse
newGetCustomDataIdentifierResponse Int
pHttpStatus_ =
  GetCustomDataIdentifierResponse'
    { $sel:arn:GetCustomDataIdentifierResponse' :: Maybe Text
arn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:createdAt:GetCustomDataIdentifierResponse' :: Maybe ISO8601
createdAt = forall a. Maybe a
Prelude.Nothing,
      $sel:deleted:GetCustomDataIdentifierResponse' :: Maybe Bool
deleted = forall a. Maybe a
Prelude.Nothing,
      $sel:description:GetCustomDataIdentifierResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:id:GetCustomDataIdentifierResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:ignoreWords:GetCustomDataIdentifierResponse' :: Maybe [Text]
ignoreWords = forall a. Maybe a
Prelude.Nothing,
      $sel:keywords:GetCustomDataIdentifierResponse' :: Maybe [Text]
keywords = forall a. Maybe a
Prelude.Nothing,
      $sel:maximumMatchDistance:GetCustomDataIdentifierResponse' :: Maybe Int
maximumMatchDistance = forall a. Maybe a
Prelude.Nothing,
      $sel:name:GetCustomDataIdentifierResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:regex:GetCustomDataIdentifierResponse' :: Maybe Text
regex = forall a. Maybe a
Prelude.Nothing,
      $sel:severityLevels:GetCustomDataIdentifierResponse' :: Maybe [SeverityLevel]
severityLevels = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:GetCustomDataIdentifierResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetCustomDataIdentifierResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the custom data identifier.
getCustomDataIdentifierResponse_arn :: Lens.Lens' GetCustomDataIdentifierResponse (Prelude.Maybe Prelude.Text)
getCustomDataIdentifierResponse_arn :: Lens' GetCustomDataIdentifierResponse (Maybe Text)
getCustomDataIdentifierResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCustomDataIdentifierResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: GetCustomDataIdentifierResponse
s@GetCustomDataIdentifierResponse' {} Maybe Text
a -> GetCustomDataIdentifierResponse
s {$sel:arn:GetCustomDataIdentifierResponse' :: Maybe Text
arn = Maybe Text
a} :: GetCustomDataIdentifierResponse)

-- | The date and time, in UTC and extended ISO 8601 format, when the custom
-- data identifier was created.
getCustomDataIdentifierResponse_createdAt :: Lens.Lens' GetCustomDataIdentifierResponse (Prelude.Maybe Prelude.UTCTime)
getCustomDataIdentifierResponse_createdAt :: Lens' GetCustomDataIdentifierResponse (Maybe UTCTime)
getCustomDataIdentifierResponse_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCustomDataIdentifierResponse' {Maybe ISO8601
createdAt :: Maybe ISO8601
$sel:createdAt:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe ISO8601
createdAt} -> Maybe ISO8601
createdAt) (\s :: GetCustomDataIdentifierResponse
s@GetCustomDataIdentifierResponse' {} Maybe ISO8601
a -> GetCustomDataIdentifierResponse
s {$sel:createdAt:GetCustomDataIdentifierResponse' :: Maybe ISO8601
createdAt = Maybe ISO8601
a} :: GetCustomDataIdentifierResponse) 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 the custom data identifier was deleted. If you delete
-- a custom data identifier, Amazon Macie doesn\'t delete it permanently.
-- Instead, it soft deletes the identifier.
getCustomDataIdentifierResponse_deleted :: Lens.Lens' GetCustomDataIdentifierResponse (Prelude.Maybe Prelude.Bool)
getCustomDataIdentifierResponse_deleted :: Lens' GetCustomDataIdentifierResponse (Maybe Bool)
getCustomDataIdentifierResponse_deleted = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCustomDataIdentifierResponse' {Maybe Bool
deleted :: Maybe Bool
$sel:deleted:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe Bool
deleted} -> Maybe Bool
deleted) (\s :: GetCustomDataIdentifierResponse
s@GetCustomDataIdentifierResponse' {} Maybe Bool
a -> GetCustomDataIdentifierResponse
s {$sel:deleted:GetCustomDataIdentifierResponse' :: Maybe Bool
deleted = Maybe Bool
a} :: GetCustomDataIdentifierResponse)

-- | The custom description of the custom data identifier.
getCustomDataIdentifierResponse_description :: Lens.Lens' GetCustomDataIdentifierResponse (Prelude.Maybe Prelude.Text)
getCustomDataIdentifierResponse_description :: Lens' GetCustomDataIdentifierResponse (Maybe Text)
getCustomDataIdentifierResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCustomDataIdentifierResponse' {Maybe Text
description :: Maybe Text
$sel:description:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: GetCustomDataIdentifierResponse
s@GetCustomDataIdentifierResponse' {} Maybe Text
a -> GetCustomDataIdentifierResponse
s {$sel:description:GetCustomDataIdentifierResponse' :: Maybe Text
description = Maybe Text
a} :: GetCustomDataIdentifierResponse)

-- | The unique identifier for the custom data identifier.
getCustomDataIdentifierResponse_id :: Lens.Lens' GetCustomDataIdentifierResponse (Prelude.Maybe Prelude.Text)
getCustomDataIdentifierResponse_id :: Lens' GetCustomDataIdentifierResponse (Maybe Text)
getCustomDataIdentifierResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCustomDataIdentifierResponse' {Maybe Text
id :: Maybe Text
$sel:id:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: GetCustomDataIdentifierResponse
s@GetCustomDataIdentifierResponse' {} Maybe Text
a -> GetCustomDataIdentifierResponse
s {$sel:id:GetCustomDataIdentifierResponse' :: Maybe Text
id = Maybe Text
a} :: GetCustomDataIdentifierResponse)

-- | An array that lists specific character sequences (/ignore words/) to
-- exclude from the results. If the text matched by the regular expression
-- contains any string in this array, Amazon Macie ignores it. Ignore words
-- are case sensitive.
getCustomDataIdentifierResponse_ignoreWords :: Lens.Lens' GetCustomDataIdentifierResponse (Prelude.Maybe [Prelude.Text])
getCustomDataIdentifierResponse_ignoreWords :: Lens' GetCustomDataIdentifierResponse (Maybe [Text])
getCustomDataIdentifierResponse_ignoreWords = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCustomDataIdentifierResponse' {Maybe [Text]
ignoreWords :: Maybe [Text]
$sel:ignoreWords:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe [Text]
ignoreWords} -> Maybe [Text]
ignoreWords) (\s :: GetCustomDataIdentifierResponse
s@GetCustomDataIdentifierResponse' {} Maybe [Text]
a -> GetCustomDataIdentifierResponse
s {$sel:ignoreWords:GetCustomDataIdentifierResponse' :: Maybe [Text]
ignoreWords = Maybe [Text]
a} :: GetCustomDataIdentifierResponse) 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

-- | An array that lists specific character sequences (/keywords/), one of
-- which must precede and be within proximity (maximumMatchDistance) of the
-- regular expression to match. Keywords aren\'t case sensitive.
getCustomDataIdentifierResponse_keywords :: Lens.Lens' GetCustomDataIdentifierResponse (Prelude.Maybe [Prelude.Text])
getCustomDataIdentifierResponse_keywords :: Lens' GetCustomDataIdentifierResponse (Maybe [Text])
getCustomDataIdentifierResponse_keywords = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCustomDataIdentifierResponse' {Maybe [Text]
keywords :: Maybe [Text]
$sel:keywords:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe [Text]
keywords} -> Maybe [Text]
keywords) (\s :: GetCustomDataIdentifierResponse
s@GetCustomDataIdentifierResponse' {} Maybe [Text]
a -> GetCustomDataIdentifierResponse
s {$sel:keywords:GetCustomDataIdentifierResponse' :: Maybe [Text]
keywords = Maybe [Text]
a} :: GetCustomDataIdentifierResponse) 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 maximum number of characters that can exist between the end of at
-- least one complete character sequence specified by the keywords array
-- and the end of the text that matches the regex pattern. If a complete
-- keyword precedes all the text that matches the pattern and the keyword
-- is within the specified distance, Amazon Macie includes the result.
-- Otherwise, Macie excludes the result.
getCustomDataIdentifierResponse_maximumMatchDistance :: Lens.Lens' GetCustomDataIdentifierResponse (Prelude.Maybe Prelude.Int)
getCustomDataIdentifierResponse_maximumMatchDistance :: Lens' GetCustomDataIdentifierResponse (Maybe Int)
getCustomDataIdentifierResponse_maximumMatchDistance = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCustomDataIdentifierResponse' {Maybe Int
maximumMatchDistance :: Maybe Int
$sel:maximumMatchDistance:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe Int
maximumMatchDistance} -> Maybe Int
maximumMatchDistance) (\s :: GetCustomDataIdentifierResponse
s@GetCustomDataIdentifierResponse' {} Maybe Int
a -> GetCustomDataIdentifierResponse
s {$sel:maximumMatchDistance:GetCustomDataIdentifierResponse' :: Maybe Int
maximumMatchDistance = Maybe Int
a} :: GetCustomDataIdentifierResponse)

-- | The custom name of the custom data identifier.
getCustomDataIdentifierResponse_name :: Lens.Lens' GetCustomDataIdentifierResponse (Prelude.Maybe Prelude.Text)
getCustomDataIdentifierResponse_name :: Lens' GetCustomDataIdentifierResponse (Maybe Text)
getCustomDataIdentifierResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCustomDataIdentifierResponse' {Maybe Text
name :: Maybe Text
$sel:name:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: GetCustomDataIdentifierResponse
s@GetCustomDataIdentifierResponse' {} Maybe Text
a -> GetCustomDataIdentifierResponse
s {$sel:name:GetCustomDataIdentifierResponse' :: Maybe Text
name = Maybe Text
a} :: GetCustomDataIdentifierResponse)

-- | The regular expression (/regex/) that defines the pattern to match.
getCustomDataIdentifierResponse_regex :: Lens.Lens' GetCustomDataIdentifierResponse (Prelude.Maybe Prelude.Text)
getCustomDataIdentifierResponse_regex :: Lens' GetCustomDataIdentifierResponse (Maybe Text)
getCustomDataIdentifierResponse_regex = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCustomDataIdentifierResponse' {Maybe Text
regex :: Maybe Text
$sel:regex:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe Text
regex} -> Maybe Text
regex) (\s :: GetCustomDataIdentifierResponse
s@GetCustomDataIdentifierResponse' {} Maybe Text
a -> GetCustomDataIdentifierResponse
s {$sel:regex:GetCustomDataIdentifierResponse' :: Maybe Text
regex = Maybe Text
a} :: GetCustomDataIdentifierResponse)

-- | Specifies the severity that\'s assigned to findings that the custom data
-- identifier produces, based on the number of occurrences of text that
-- matches the custom data identifier\'s detection criteria. By default,
-- Amazon Macie creates findings for S3 objects that contain at least one
-- occurrence of text that matches the detection criteria, and Macie
-- assigns the MEDIUM severity to those findings.
getCustomDataIdentifierResponse_severityLevels :: Lens.Lens' GetCustomDataIdentifierResponse (Prelude.Maybe [SeverityLevel])
getCustomDataIdentifierResponse_severityLevels :: Lens' GetCustomDataIdentifierResponse (Maybe [SeverityLevel])
getCustomDataIdentifierResponse_severityLevels = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCustomDataIdentifierResponse' {Maybe [SeverityLevel]
severityLevels :: Maybe [SeverityLevel]
$sel:severityLevels:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe [SeverityLevel]
severityLevels} -> Maybe [SeverityLevel]
severityLevels) (\s :: GetCustomDataIdentifierResponse
s@GetCustomDataIdentifierResponse' {} Maybe [SeverityLevel]
a -> GetCustomDataIdentifierResponse
s {$sel:severityLevels:GetCustomDataIdentifierResponse' :: Maybe [SeverityLevel]
severityLevels = Maybe [SeverityLevel]
a} :: GetCustomDataIdentifierResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | A map of key-value pairs that identifies the tags (keys and values) that
-- are associated with the custom data identifier.
getCustomDataIdentifierResponse_tags :: Lens.Lens' GetCustomDataIdentifierResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
getCustomDataIdentifierResponse_tags :: Lens' GetCustomDataIdentifierResponse (Maybe (HashMap Text Text))
getCustomDataIdentifierResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCustomDataIdentifierResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: GetCustomDataIdentifierResponse
s@GetCustomDataIdentifierResponse' {} Maybe (HashMap Text Text)
a -> GetCustomDataIdentifierResponse
s {$sel:tags:GetCustomDataIdentifierResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: GetCustomDataIdentifierResponse) 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 response's http status code.
getCustomDataIdentifierResponse_httpStatus :: Lens.Lens' GetCustomDataIdentifierResponse Prelude.Int
getCustomDataIdentifierResponse_httpStatus :: Lens' GetCustomDataIdentifierResponse Int
getCustomDataIdentifierResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCustomDataIdentifierResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetCustomDataIdentifierResponse
s@GetCustomDataIdentifierResponse' {} Int
a -> GetCustomDataIdentifierResponse
s {$sel:httpStatus:GetCustomDataIdentifierResponse' :: Int
httpStatus = Int
a} :: GetCustomDataIdentifierResponse)

instance
  Prelude.NFData
    GetCustomDataIdentifierResponse
  where
  rnf :: GetCustomDataIdentifierResponse -> ()
rnf GetCustomDataIdentifierResponse' {Int
Maybe Bool
Maybe Int
Maybe [Text]
Maybe [SeverityLevel]
Maybe Text
Maybe (HashMap Text Text)
Maybe ISO8601
httpStatus :: Int
tags :: Maybe (HashMap Text Text)
severityLevels :: Maybe [SeverityLevel]
regex :: Maybe Text
name :: Maybe Text
maximumMatchDistance :: Maybe Int
keywords :: Maybe [Text]
ignoreWords :: Maybe [Text]
id :: Maybe Text
description :: Maybe Text
deleted :: Maybe Bool
createdAt :: Maybe ISO8601
arn :: Maybe Text
$sel:httpStatus:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Int
$sel:tags:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe (HashMap Text Text)
$sel:severityLevels:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe [SeverityLevel]
$sel:regex:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe Text
$sel:name:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe Text
$sel:maximumMatchDistance:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe Int
$sel:keywords:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe [Text]
$sel:ignoreWords:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe [Text]
$sel:id:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe Text
$sel:description:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe Text
$sel:deleted:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe Bool
$sel:createdAt:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe ISO8601
$sel:arn:GetCustomDataIdentifierResponse' :: GetCustomDataIdentifierResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
createdAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
deleted
      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
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
ignoreWords
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
keywords
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maximumMatchDistance
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
regex
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [SeverityLevel]
severityLevels
      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 Int
httpStatus