{-# 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.Comprehend.Types.PiiEntitiesDetectionJobProperties
-- 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.Comprehend.Types.PiiEntitiesDetectionJobProperties where

import Amazonka.Comprehend.Types.InputDataConfig
import Amazonka.Comprehend.Types.JobStatus
import Amazonka.Comprehend.Types.LanguageCode
import Amazonka.Comprehend.Types.PiiEntitiesDetectionMode
import Amazonka.Comprehend.Types.PiiOutputDataConfig
import Amazonka.Comprehend.Types.RedactionConfig
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

-- | Provides information about a PII entities detection job.
--
-- /See:/ 'newPiiEntitiesDetectionJobProperties' smart constructor.
data PiiEntitiesDetectionJobProperties = PiiEntitiesDetectionJobProperties'
  { -- | The Amazon Resource Name (ARN) that gives Amazon Comprehend read access
    -- to your input data.
    PiiEntitiesDetectionJobProperties -> Maybe Text
dataAccessRoleArn :: Prelude.Maybe Prelude.Text,
    -- | The time that the PII entities detection job completed.
    PiiEntitiesDetectionJobProperties -> Maybe POSIX
endTime :: Prelude.Maybe Data.POSIX,
    -- | The input properties for a PII entities detection job.
    PiiEntitiesDetectionJobProperties -> Maybe InputDataConfig
inputDataConfig :: Prelude.Maybe InputDataConfig,
    -- | The Amazon Resource Name (ARN) of the PII entities detection job. It is
    -- a unique, fully qualified identifier for the job. It includes the AWS
    -- account, Region, and the job ID. The format of the ARN is as follows:
    --
    -- @arn:\<partition>:comprehend:\<region>:\<account-id>:pii-entities-detection-job\/\<job-id>@
    --
    -- The following is an example job ARN:
    --
    -- @arn:aws:comprehend:us-west-2:111122223333:pii-entities-detection-job\/1234abcd12ab34cd56ef1234567890ab@
    PiiEntitiesDetectionJobProperties -> Maybe Text
jobArn :: Prelude.Maybe Prelude.Text,
    -- | The identifier assigned to the PII entities detection job.
    PiiEntitiesDetectionJobProperties -> Maybe Text
jobId :: Prelude.Maybe Prelude.Text,
    -- | The name that you assigned the PII entities detection job.
    PiiEntitiesDetectionJobProperties -> Maybe Text
jobName :: Prelude.Maybe Prelude.Text,
    -- | The current status of the PII entities detection job. If the status is
    -- @FAILED@, the @Message@ field shows the reason for the failure.
    PiiEntitiesDetectionJobProperties -> Maybe JobStatus
jobStatus :: Prelude.Maybe JobStatus,
    -- | The language code of the input documents
    PiiEntitiesDetectionJobProperties -> Maybe LanguageCode
languageCode :: Prelude.Maybe LanguageCode,
    -- | A description of the status of a job.
    PiiEntitiesDetectionJobProperties -> Maybe Text
message :: Prelude.Maybe Prelude.Text,
    -- | Specifies whether the output provides the locations (offsets) of PII
    -- entities or a file in which PII entities are redacted.
    PiiEntitiesDetectionJobProperties -> Maybe PiiEntitiesDetectionMode
mode :: Prelude.Maybe PiiEntitiesDetectionMode,
    -- | The output data configuration that you supplied when you created the PII
    -- entities detection job.
    PiiEntitiesDetectionJobProperties -> Maybe PiiOutputDataConfig
outputDataConfig :: Prelude.Maybe PiiOutputDataConfig,
    -- | Provides configuration parameters for PII entity redaction.
    --
    -- This parameter is required if you set the @Mode@ parameter to
    -- @ONLY_REDACTION@. In that case, you must provide a @RedactionConfig@
    -- definition that includes the @PiiEntityTypes@ parameter.
    PiiEntitiesDetectionJobProperties -> Maybe RedactionConfig
redactionConfig :: Prelude.Maybe RedactionConfig,
    -- | The time that the PII entities detection job was submitted for
    -- processing.
    PiiEntitiesDetectionJobProperties -> Maybe POSIX
submitTime :: Prelude.Maybe Data.POSIX
  }
  deriving (PiiEntitiesDetectionJobProperties
-> PiiEntitiesDetectionJobProperties -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PiiEntitiesDetectionJobProperties
-> PiiEntitiesDetectionJobProperties -> Bool
$c/= :: PiiEntitiesDetectionJobProperties
-> PiiEntitiesDetectionJobProperties -> Bool
== :: PiiEntitiesDetectionJobProperties
-> PiiEntitiesDetectionJobProperties -> Bool
$c== :: PiiEntitiesDetectionJobProperties
-> PiiEntitiesDetectionJobProperties -> Bool
Prelude.Eq, ReadPrec [PiiEntitiesDetectionJobProperties]
ReadPrec PiiEntitiesDetectionJobProperties
Int -> ReadS PiiEntitiesDetectionJobProperties
ReadS [PiiEntitiesDetectionJobProperties]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PiiEntitiesDetectionJobProperties]
$creadListPrec :: ReadPrec [PiiEntitiesDetectionJobProperties]
readPrec :: ReadPrec PiiEntitiesDetectionJobProperties
$creadPrec :: ReadPrec PiiEntitiesDetectionJobProperties
readList :: ReadS [PiiEntitiesDetectionJobProperties]
$creadList :: ReadS [PiiEntitiesDetectionJobProperties]
readsPrec :: Int -> ReadS PiiEntitiesDetectionJobProperties
$creadsPrec :: Int -> ReadS PiiEntitiesDetectionJobProperties
Prelude.Read, Int -> PiiEntitiesDetectionJobProperties -> ShowS
[PiiEntitiesDetectionJobProperties] -> ShowS
PiiEntitiesDetectionJobProperties -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PiiEntitiesDetectionJobProperties] -> ShowS
$cshowList :: [PiiEntitiesDetectionJobProperties] -> ShowS
show :: PiiEntitiesDetectionJobProperties -> String
$cshow :: PiiEntitiesDetectionJobProperties -> String
showsPrec :: Int -> PiiEntitiesDetectionJobProperties -> ShowS
$cshowsPrec :: Int -> PiiEntitiesDetectionJobProperties -> ShowS
Prelude.Show, forall x.
Rep PiiEntitiesDetectionJobProperties x
-> PiiEntitiesDetectionJobProperties
forall x.
PiiEntitiesDetectionJobProperties
-> Rep PiiEntitiesDetectionJobProperties x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PiiEntitiesDetectionJobProperties x
-> PiiEntitiesDetectionJobProperties
$cfrom :: forall x.
PiiEntitiesDetectionJobProperties
-> Rep PiiEntitiesDetectionJobProperties x
Prelude.Generic)

-- |
-- Create a value of 'PiiEntitiesDetectionJobProperties' 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:
--
-- 'dataAccessRoleArn', 'piiEntitiesDetectionJobProperties_dataAccessRoleArn' - The Amazon Resource Name (ARN) that gives Amazon Comprehend read access
-- to your input data.
--
-- 'endTime', 'piiEntitiesDetectionJobProperties_endTime' - The time that the PII entities detection job completed.
--
-- 'inputDataConfig', 'piiEntitiesDetectionJobProperties_inputDataConfig' - The input properties for a PII entities detection job.
--
-- 'jobArn', 'piiEntitiesDetectionJobProperties_jobArn' - The Amazon Resource Name (ARN) of the PII entities detection job. It is
-- a unique, fully qualified identifier for the job. It includes the AWS
-- account, Region, and the job ID. The format of the ARN is as follows:
--
-- @arn:\<partition>:comprehend:\<region>:\<account-id>:pii-entities-detection-job\/\<job-id>@
--
-- The following is an example job ARN:
--
-- @arn:aws:comprehend:us-west-2:111122223333:pii-entities-detection-job\/1234abcd12ab34cd56ef1234567890ab@
--
-- 'jobId', 'piiEntitiesDetectionJobProperties_jobId' - The identifier assigned to the PII entities detection job.
--
-- 'jobName', 'piiEntitiesDetectionJobProperties_jobName' - The name that you assigned the PII entities detection job.
--
-- 'jobStatus', 'piiEntitiesDetectionJobProperties_jobStatus' - The current status of the PII entities detection job. If the status is
-- @FAILED@, the @Message@ field shows the reason for the failure.
--
-- 'languageCode', 'piiEntitiesDetectionJobProperties_languageCode' - The language code of the input documents
--
-- 'message', 'piiEntitiesDetectionJobProperties_message' - A description of the status of a job.
--
-- 'mode', 'piiEntitiesDetectionJobProperties_mode' - Specifies whether the output provides the locations (offsets) of PII
-- entities or a file in which PII entities are redacted.
--
-- 'outputDataConfig', 'piiEntitiesDetectionJobProperties_outputDataConfig' - The output data configuration that you supplied when you created the PII
-- entities detection job.
--
-- 'redactionConfig', 'piiEntitiesDetectionJobProperties_redactionConfig' - Provides configuration parameters for PII entity redaction.
--
-- This parameter is required if you set the @Mode@ parameter to
-- @ONLY_REDACTION@. In that case, you must provide a @RedactionConfig@
-- definition that includes the @PiiEntityTypes@ parameter.
--
-- 'submitTime', 'piiEntitiesDetectionJobProperties_submitTime' - The time that the PII entities detection job was submitted for
-- processing.
newPiiEntitiesDetectionJobProperties ::
  PiiEntitiesDetectionJobProperties
newPiiEntitiesDetectionJobProperties :: PiiEntitiesDetectionJobProperties
newPiiEntitiesDetectionJobProperties =
  PiiEntitiesDetectionJobProperties'
    { $sel:dataAccessRoleArn:PiiEntitiesDetectionJobProperties' :: Maybe Text
dataAccessRoleArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:endTime:PiiEntitiesDetectionJobProperties' :: Maybe POSIX
endTime = forall a. Maybe a
Prelude.Nothing,
      $sel:inputDataConfig:PiiEntitiesDetectionJobProperties' :: Maybe InputDataConfig
inputDataConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:jobArn:PiiEntitiesDetectionJobProperties' :: Maybe Text
jobArn = forall a. Maybe a
Prelude.Nothing,
      $sel:jobId:PiiEntitiesDetectionJobProperties' :: Maybe Text
jobId = forall a. Maybe a
Prelude.Nothing,
      $sel:jobName:PiiEntitiesDetectionJobProperties' :: Maybe Text
jobName = forall a. Maybe a
Prelude.Nothing,
      $sel:jobStatus:PiiEntitiesDetectionJobProperties' :: Maybe JobStatus
jobStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:languageCode:PiiEntitiesDetectionJobProperties' :: Maybe LanguageCode
languageCode = forall a. Maybe a
Prelude.Nothing,
      $sel:message:PiiEntitiesDetectionJobProperties' :: Maybe Text
message = forall a. Maybe a
Prelude.Nothing,
      $sel:mode:PiiEntitiesDetectionJobProperties' :: Maybe PiiEntitiesDetectionMode
mode = forall a. Maybe a
Prelude.Nothing,
      $sel:outputDataConfig:PiiEntitiesDetectionJobProperties' :: Maybe PiiOutputDataConfig
outputDataConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:redactionConfig:PiiEntitiesDetectionJobProperties' :: Maybe RedactionConfig
redactionConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:submitTime:PiiEntitiesDetectionJobProperties' :: Maybe POSIX
submitTime = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Name (ARN) that gives Amazon Comprehend read access
-- to your input data.
piiEntitiesDetectionJobProperties_dataAccessRoleArn :: Lens.Lens' PiiEntitiesDetectionJobProperties (Prelude.Maybe Prelude.Text)
piiEntitiesDetectionJobProperties_dataAccessRoleArn :: Lens' PiiEntitiesDetectionJobProperties (Maybe Text)
piiEntitiesDetectionJobProperties_dataAccessRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PiiEntitiesDetectionJobProperties' {Maybe Text
dataAccessRoleArn :: Maybe Text
$sel:dataAccessRoleArn:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe Text
dataAccessRoleArn} -> Maybe Text
dataAccessRoleArn) (\s :: PiiEntitiesDetectionJobProperties
s@PiiEntitiesDetectionJobProperties' {} Maybe Text
a -> PiiEntitiesDetectionJobProperties
s {$sel:dataAccessRoleArn:PiiEntitiesDetectionJobProperties' :: Maybe Text
dataAccessRoleArn = Maybe Text
a} :: PiiEntitiesDetectionJobProperties)

-- | The time that the PII entities detection job completed.
piiEntitiesDetectionJobProperties_endTime :: Lens.Lens' PiiEntitiesDetectionJobProperties (Prelude.Maybe Prelude.UTCTime)
piiEntitiesDetectionJobProperties_endTime :: Lens' PiiEntitiesDetectionJobProperties (Maybe UTCTime)
piiEntitiesDetectionJobProperties_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PiiEntitiesDetectionJobProperties' {Maybe POSIX
endTime :: Maybe POSIX
$sel:endTime:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe POSIX
endTime} -> Maybe POSIX
endTime) (\s :: PiiEntitiesDetectionJobProperties
s@PiiEntitiesDetectionJobProperties' {} Maybe POSIX
a -> PiiEntitiesDetectionJobProperties
s {$sel:endTime:PiiEntitiesDetectionJobProperties' :: Maybe POSIX
endTime = Maybe POSIX
a} :: PiiEntitiesDetectionJobProperties) 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

-- | The input properties for a PII entities detection job.
piiEntitiesDetectionJobProperties_inputDataConfig :: Lens.Lens' PiiEntitiesDetectionJobProperties (Prelude.Maybe InputDataConfig)
piiEntitiesDetectionJobProperties_inputDataConfig :: Lens' PiiEntitiesDetectionJobProperties (Maybe InputDataConfig)
piiEntitiesDetectionJobProperties_inputDataConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PiiEntitiesDetectionJobProperties' {Maybe InputDataConfig
inputDataConfig :: Maybe InputDataConfig
$sel:inputDataConfig:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe InputDataConfig
inputDataConfig} -> Maybe InputDataConfig
inputDataConfig) (\s :: PiiEntitiesDetectionJobProperties
s@PiiEntitiesDetectionJobProperties' {} Maybe InputDataConfig
a -> PiiEntitiesDetectionJobProperties
s {$sel:inputDataConfig:PiiEntitiesDetectionJobProperties' :: Maybe InputDataConfig
inputDataConfig = Maybe InputDataConfig
a} :: PiiEntitiesDetectionJobProperties)

-- | The Amazon Resource Name (ARN) of the PII entities detection job. It is
-- a unique, fully qualified identifier for the job. It includes the AWS
-- account, Region, and the job ID. The format of the ARN is as follows:
--
-- @arn:\<partition>:comprehend:\<region>:\<account-id>:pii-entities-detection-job\/\<job-id>@
--
-- The following is an example job ARN:
--
-- @arn:aws:comprehend:us-west-2:111122223333:pii-entities-detection-job\/1234abcd12ab34cd56ef1234567890ab@
piiEntitiesDetectionJobProperties_jobArn :: Lens.Lens' PiiEntitiesDetectionJobProperties (Prelude.Maybe Prelude.Text)
piiEntitiesDetectionJobProperties_jobArn :: Lens' PiiEntitiesDetectionJobProperties (Maybe Text)
piiEntitiesDetectionJobProperties_jobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PiiEntitiesDetectionJobProperties' {Maybe Text
jobArn :: Maybe Text
$sel:jobArn:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe Text
jobArn} -> Maybe Text
jobArn) (\s :: PiiEntitiesDetectionJobProperties
s@PiiEntitiesDetectionJobProperties' {} Maybe Text
a -> PiiEntitiesDetectionJobProperties
s {$sel:jobArn:PiiEntitiesDetectionJobProperties' :: Maybe Text
jobArn = Maybe Text
a} :: PiiEntitiesDetectionJobProperties)

-- | The identifier assigned to the PII entities detection job.
piiEntitiesDetectionJobProperties_jobId :: Lens.Lens' PiiEntitiesDetectionJobProperties (Prelude.Maybe Prelude.Text)
piiEntitiesDetectionJobProperties_jobId :: Lens' PiiEntitiesDetectionJobProperties (Maybe Text)
piiEntitiesDetectionJobProperties_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PiiEntitiesDetectionJobProperties' {Maybe Text
jobId :: Maybe Text
$sel:jobId:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe Text
jobId} -> Maybe Text
jobId) (\s :: PiiEntitiesDetectionJobProperties
s@PiiEntitiesDetectionJobProperties' {} Maybe Text
a -> PiiEntitiesDetectionJobProperties
s {$sel:jobId:PiiEntitiesDetectionJobProperties' :: Maybe Text
jobId = Maybe Text
a} :: PiiEntitiesDetectionJobProperties)

-- | The name that you assigned the PII entities detection job.
piiEntitiesDetectionJobProperties_jobName :: Lens.Lens' PiiEntitiesDetectionJobProperties (Prelude.Maybe Prelude.Text)
piiEntitiesDetectionJobProperties_jobName :: Lens' PiiEntitiesDetectionJobProperties (Maybe Text)
piiEntitiesDetectionJobProperties_jobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PiiEntitiesDetectionJobProperties' {Maybe Text
jobName :: Maybe Text
$sel:jobName:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe Text
jobName} -> Maybe Text
jobName) (\s :: PiiEntitiesDetectionJobProperties
s@PiiEntitiesDetectionJobProperties' {} Maybe Text
a -> PiiEntitiesDetectionJobProperties
s {$sel:jobName:PiiEntitiesDetectionJobProperties' :: Maybe Text
jobName = Maybe Text
a} :: PiiEntitiesDetectionJobProperties)

-- | The current status of the PII entities detection job. If the status is
-- @FAILED@, the @Message@ field shows the reason for the failure.
piiEntitiesDetectionJobProperties_jobStatus :: Lens.Lens' PiiEntitiesDetectionJobProperties (Prelude.Maybe JobStatus)
piiEntitiesDetectionJobProperties_jobStatus :: Lens' PiiEntitiesDetectionJobProperties (Maybe JobStatus)
piiEntitiesDetectionJobProperties_jobStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PiiEntitiesDetectionJobProperties' {Maybe JobStatus
jobStatus :: Maybe JobStatus
$sel:jobStatus:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe JobStatus
jobStatus} -> Maybe JobStatus
jobStatus) (\s :: PiiEntitiesDetectionJobProperties
s@PiiEntitiesDetectionJobProperties' {} Maybe JobStatus
a -> PiiEntitiesDetectionJobProperties
s {$sel:jobStatus:PiiEntitiesDetectionJobProperties' :: Maybe JobStatus
jobStatus = Maybe JobStatus
a} :: PiiEntitiesDetectionJobProperties)

-- | The language code of the input documents
piiEntitiesDetectionJobProperties_languageCode :: Lens.Lens' PiiEntitiesDetectionJobProperties (Prelude.Maybe LanguageCode)
piiEntitiesDetectionJobProperties_languageCode :: Lens' PiiEntitiesDetectionJobProperties (Maybe LanguageCode)
piiEntitiesDetectionJobProperties_languageCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PiiEntitiesDetectionJobProperties' {Maybe LanguageCode
languageCode :: Maybe LanguageCode
$sel:languageCode:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe LanguageCode
languageCode} -> Maybe LanguageCode
languageCode) (\s :: PiiEntitiesDetectionJobProperties
s@PiiEntitiesDetectionJobProperties' {} Maybe LanguageCode
a -> PiiEntitiesDetectionJobProperties
s {$sel:languageCode:PiiEntitiesDetectionJobProperties' :: Maybe LanguageCode
languageCode = Maybe LanguageCode
a} :: PiiEntitiesDetectionJobProperties)

-- | A description of the status of a job.
piiEntitiesDetectionJobProperties_message :: Lens.Lens' PiiEntitiesDetectionJobProperties (Prelude.Maybe Prelude.Text)
piiEntitiesDetectionJobProperties_message :: Lens' PiiEntitiesDetectionJobProperties (Maybe Text)
piiEntitiesDetectionJobProperties_message = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PiiEntitiesDetectionJobProperties' {Maybe Text
message :: Maybe Text
$sel:message:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe Text
message} -> Maybe Text
message) (\s :: PiiEntitiesDetectionJobProperties
s@PiiEntitiesDetectionJobProperties' {} Maybe Text
a -> PiiEntitiesDetectionJobProperties
s {$sel:message:PiiEntitiesDetectionJobProperties' :: Maybe Text
message = Maybe Text
a} :: PiiEntitiesDetectionJobProperties)

-- | Specifies whether the output provides the locations (offsets) of PII
-- entities or a file in which PII entities are redacted.
piiEntitiesDetectionJobProperties_mode :: Lens.Lens' PiiEntitiesDetectionJobProperties (Prelude.Maybe PiiEntitiesDetectionMode)
piiEntitiesDetectionJobProperties_mode :: Lens'
  PiiEntitiesDetectionJobProperties (Maybe PiiEntitiesDetectionMode)
piiEntitiesDetectionJobProperties_mode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PiiEntitiesDetectionJobProperties' {Maybe PiiEntitiesDetectionMode
mode :: Maybe PiiEntitiesDetectionMode
$sel:mode:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe PiiEntitiesDetectionMode
mode} -> Maybe PiiEntitiesDetectionMode
mode) (\s :: PiiEntitiesDetectionJobProperties
s@PiiEntitiesDetectionJobProperties' {} Maybe PiiEntitiesDetectionMode
a -> PiiEntitiesDetectionJobProperties
s {$sel:mode:PiiEntitiesDetectionJobProperties' :: Maybe PiiEntitiesDetectionMode
mode = Maybe PiiEntitiesDetectionMode
a} :: PiiEntitiesDetectionJobProperties)

-- | The output data configuration that you supplied when you created the PII
-- entities detection job.
piiEntitiesDetectionJobProperties_outputDataConfig :: Lens.Lens' PiiEntitiesDetectionJobProperties (Prelude.Maybe PiiOutputDataConfig)
piiEntitiesDetectionJobProperties_outputDataConfig :: Lens' PiiEntitiesDetectionJobProperties (Maybe PiiOutputDataConfig)
piiEntitiesDetectionJobProperties_outputDataConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PiiEntitiesDetectionJobProperties' {Maybe PiiOutputDataConfig
outputDataConfig :: Maybe PiiOutputDataConfig
$sel:outputDataConfig:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe PiiOutputDataConfig
outputDataConfig} -> Maybe PiiOutputDataConfig
outputDataConfig) (\s :: PiiEntitiesDetectionJobProperties
s@PiiEntitiesDetectionJobProperties' {} Maybe PiiOutputDataConfig
a -> PiiEntitiesDetectionJobProperties
s {$sel:outputDataConfig:PiiEntitiesDetectionJobProperties' :: Maybe PiiOutputDataConfig
outputDataConfig = Maybe PiiOutputDataConfig
a} :: PiiEntitiesDetectionJobProperties)

-- | Provides configuration parameters for PII entity redaction.
--
-- This parameter is required if you set the @Mode@ parameter to
-- @ONLY_REDACTION@. In that case, you must provide a @RedactionConfig@
-- definition that includes the @PiiEntityTypes@ parameter.
piiEntitiesDetectionJobProperties_redactionConfig :: Lens.Lens' PiiEntitiesDetectionJobProperties (Prelude.Maybe RedactionConfig)
piiEntitiesDetectionJobProperties_redactionConfig :: Lens' PiiEntitiesDetectionJobProperties (Maybe RedactionConfig)
piiEntitiesDetectionJobProperties_redactionConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PiiEntitiesDetectionJobProperties' {Maybe RedactionConfig
redactionConfig :: Maybe RedactionConfig
$sel:redactionConfig:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe RedactionConfig
redactionConfig} -> Maybe RedactionConfig
redactionConfig) (\s :: PiiEntitiesDetectionJobProperties
s@PiiEntitiesDetectionJobProperties' {} Maybe RedactionConfig
a -> PiiEntitiesDetectionJobProperties
s {$sel:redactionConfig:PiiEntitiesDetectionJobProperties' :: Maybe RedactionConfig
redactionConfig = Maybe RedactionConfig
a} :: PiiEntitiesDetectionJobProperties)

-- | The time that the PII entities detection job was submitted for
-- processing.
piiEntitiesDetectionJobProperties_submitTime :: Lens.Lens' PiiEntitiesDetectionJobProperties (Prelude.Maybe Prelude.UTCTime)
piiEntitiesDetectionJobProperties_submitTime :: Lens' PiiEntitiesDetectionJobProperties (Maybe UTCTime)
piiEntitiesDetectionJobProperties_submitTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PiiEntitiesDetectionJobProperties' {Maybe POSIX
submitTime :: Maybe POSIX
$sel:submitTime:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe POSIX
submitTime} -> Maybe POSIX
submitTime) (\s :: PiiEntitiesDetectionJobProperties
s@PiiEntitiesDetectionJobProperties' {} Maybe POSIX
a -> PiiEntitiesDetectionJobProperties
s {$sel:submitTime:PiiEntitiesDetectionJobProperties' :: Maybe POSIX
submitTime = Maybe POSIX
a} :: PiiEntitiesDetectionJobProperties) 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

instance
  Data.FromJSON
    PiiEntitiesDetectionJobProperties
  where
  parseJSON :: Value -> Parser PiiEntitiesDetectionJobProperties
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"PiiEntitiesDetectionJobProperties"
      ( \Object
x ->
          Maybe Text
-> Maybe POSIX
-> Maybe InputDataConfig
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe JobStatus
-> Maybe LanguageCode
-> Maybe Text
-> Maybe PiiEntitiesDetectionMode
-> Maybe PiiOutputDataConfig
-> Maybe RedactionConfig
-> Maybe POSIX
-> PiiEntitiesDetectionJobProperties
PiiEntitiesDetectionJobProperties'
            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
"DataAccessRoleArn")
            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
"EndTime")
            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
"InputDataConfig")
            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
"JobArn")
            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
"JobId")
            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
"JobName")
            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
"JobStatus")
            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
"LanguageCode")
            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
"Message")
            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
"Mode")
            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
"OutputDataConfig")
            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
"RedactionConfig")
            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
"SubmitTime")
      )

instance
  Prelude.Hashable
    PiiEntitiesDetectionJobProperties
  where
  hashWithSalt :: Int -> PiiEntitiesDetectionJobProperties -> Int
hashWithSalt
    Int
_salt
    PiiEntitiesDetectionJobProperties' {Maybe Text
Maybe POSIX
Maybe InputDataConfig
Maybe JobStatus
Maybe LanguageCode
Maybe PiiEntitiesDetectionMode
Maybe PiiOutputDataConfig
Maybe RedactionConfig
submitTime :: Maybe POSIX
redactionConfig :: Maybe RedactionConfig
outputDataConfig :: Maybe PiiOutputDataConfig
mode :: Maybe PiiEntitiesDetectionMode
message :: Maybe Text
languageCode :: Maybe LanguageCode
jobStatus :: Maybe JobStatus
jobName :: Maybe Text
jobId :: Maybe Text
jobArn :: Maybe Text
inputDataConfig :: Maybe InputDataConfig
endTime :: Maybe POSIX
dataAccessRoleArn :: Maybe Text
$sel:submitTime:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe POSIX
$sel:redactionConfig:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe RedactionConfig
$sel:outputDataConfig:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe PiiOutputDataConfig
$sel:mode:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe PiiEntitiesDetectionMode
$sel:message:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe Text
$sel:languageCode:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe LanguageCode
$sel:jobStatus:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe JobStatus
$sel:jobName:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe Text
$sel:jobId:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe Text
$sel:jobArn:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe Text
$sel:inputDataConfig:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe InputDataConfig
$sel:endTime:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe POSIX
$sel:dataAccessRoleArn:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dataAccessRoleArn
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
endTime
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InputDataConfig
inputDataConfig
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobArn
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobName
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JobStatus
jobStatus
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LanguageCode
languageCode
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
message
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PiiEntitiesDetectionMode
mode
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PiiOutputDataConfig
outputDataConfig
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RedactionConfig
redactionConfig
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
submitTime

instance
  Prelude.NFData
    PiiEntitiesDetectionJobProperties
  where
  rnf :: PiiEntitiesDetectionJobProperties -> ()
rnf PiiEntitiesDetectionJobProperties' {Maybe Text
Maybe POSIX
Maybe InputDataConfig
Maybe JobStatus
Maybe LanguageCode
Maybe PiiEntitiesDetectionMode
Maybe PiiOutputDataConfig
Maybe RedactionConfig
submitTime :: Maybe POSIX
redactionConfig :: Maybe RedactionConfig
outputDataConfig :: Maybe PiiOutputDataConfig
mode :: Maybe PiiEntitiesDetectionMode
message :: Maybe Text
languageCode :: Maybe LanguageCode
jobStatus :: Maybe JobStatus
jobName :: Maybe Text
jobId :: Maybe Text
jobArn :: Maybe Text
inputDataConfig :: Maybe InputDataConfig
endTime :: Maybe POSIX
dataAccessRoleArn :: Maybe Text
$sel:submitTime:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe POSIX
$sel:redactionConfig:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe RedactionConfig
$sel:outputDataConfig:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe PiiOutputDataConfig
$sel:mode:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe PiiEntitiesDetectionMode
$sel:message:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe Text
$sel:languageCode:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe LanguageCode
$sel:jobStatus:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe JobStatus
$sel:jobName:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe Text
$sel:jobId:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe Text
$sel:jobArn:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe Text
$sel:inputDataConfig:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe InputDataConfig
$sel:endTime:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe POSIX
$sel:dataAccessRoleArn:PiiEntitiesDetectionJobProperties' :: PiiEntitiesDetectionJobProperties -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dataAccessRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
endTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InputDataConfig
inputDataConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JobStatus
jobStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LanguageCode
languageCode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
message
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PiiEntitiesDetectionMode
mode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PiiOutputDataConfig
outputDataConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RedactionConfig
redactionConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
submitTime