{-# 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.CreateClassificationJob
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates and defines the settings for a classification job.
module Amazonka.MacieV2.CreateClassificationJob
  ( -- * Creating a Request
    CreateClassificationJob (..),
    newCreateClassificationJob,

    -- * Request Lenses
    createClassificationJob_allowListIds,
    createClassificationJob_customDataIdentifierIds,
    createClassificationJob_description,
    createClassificationJob_initialRun,
    createClassificationJob_managedDataIdentifierIds,
    createClassificationJob_managedDataIdentifierSelector,
    createClassificationJob_samplingPercentage,
    createClassificationJob_scheduleFrequency,
    createClassificationJob_tags,
    createClassificationJob_s3JobDefinition,
    createClassificationJob_jobType,
    createClassificationJob_clientToken,
    createClassificationJob_name,

    -- * Destructuring the Response
    CreateClassificationJobResponse (..),
    newCreateClassificationJobResponse,

    -- * Response Lenses
    createClassificationJobResponse_jobArn,
    createClassificationJobResponse_jobId,
    createClassificationJobResponse_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:/ 'newCreateClassificationJob' smart constructor.
data CreateClassificationJob = CreateClassificationJob'
  { -- | An array of unique identifiers, one for each allow list for the job to
    -- use when it analyzes data.
    CreateClassificationJob -> Maybe [Text]
allowListIds :: Prelude.Maybe [Prelude.Text],
    -- | An array of unique identifiers, one for each custom data identifier for
    -- the job to use when it analyzes data. To use only managed data
    -- identifiers, don\'t specify a value for this property and specify a
    -- value other than NONE for the managedDataIdentifierSelector property.
    CreateClassificationJob -> Maybe [Text]
customDataIdentifierIds :: Prelude.Maybe [Prelude.Text],
    -- | A custom description of the job. The description can contain as many as
    -- 200 characters.
    CreateClassificationJob -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | For a recurring job, specifies whether to analyze all existing, eligible
    -- objects immediately after the job is created (true). To analyze only
    -- those objects that are created or changed after you create the job and
    -- before the job\'s first scheduled run, set this value to false.
    --
    -- If you configure the job to run only once, don\'t specify a value for
    -- this property.
    CreateClassificationJob -> Maybe Bool
initialRun :: Prelude.Maybe Prelude.Bool,
    -- | An array of unique identifiers, one for each managed data identifier for
    -- the job to include (use) or exclude (not use) when it analyzes data.
    -- Inclusion or exclusion depends on the managed data identifier selection
    -- type that you specify for the job (managedDataIdentifierSelector).
    --
    -- To retrieve a list of valid values for this property, use the
    -- ListManagedDataIdentifiers operation.
    CreateClassificationJob -> Maybe [Text]
managedDataIdentifierIds :: Prelude.Maybe [Prelude.Text],
    -- | The selection type to apply when determining which managed data
    -- identifiers the job uses to analyze data. Valid values are:
    --
    -- -   ALL - Use all the managed data identifiers that Amazon Macie
    --     provides. If you specify this value, don\'t specify any values for
    --     the managedDataIdentifierIds property.
    --
    -- -   EXCLUDE - Use all the managed data identifiers that Macie provides
    --     except the managed data identifiers specified by the
    --     managedDataIdentifierIds property.
    --
    -- -   INCLUDE - Use only the managed data identifiers specified by the
    --     managedDataIdentifierIds property.
    --
    -- -   NONE - Don\'t use any managed data identifiers. If you specify this
    --     value, specify at least one custom data identifier for the job
    --     (customDataIdentifierIds) and don\'t specify any values for the
    --     managedDataIdentifierIds property.
    --
    -- If you don\'t specify a value for this property, the job uses all
    -- managed data identifiers. If you don\'t specify a value for this
    -- property or you specify ALL or EXCLUDE for a recurring job, the job also
    -- uses new managed data identifiers as they are released.
    CreateClassificationJob -> Maybe ManagedDataIdentifierSelector
managedDataIdentifierSelector :: Prelude.Maybe ManagedDataIdentifierSelector,
    -- | The sampling depth, as a percentage, for the job to apply when
    -- processing objects. This value determines the percentage of eligible
    -- objects that the job analyzes. If this value is less than 100, Amazon
    -- Macie selects the objects to analyze at random, up to the specified
    -- percentage, and analyzes all the data in those objects.
    CreateClassificationJob -> Maybe Int
samplingPercentage :: Prelude.Maybe Prelude.Int,
    -- | The recurrence pattern for running the job. To run the job only once,
    -- don\'t specify a value for this property and set the value for the
    -- jobType property to ONE_TIME.
    CreateClassificationJob -> Maybe JobScheduleFrequency
scheduleFrequency :: Prelude.Maybe JobScheduleFrequency,
    -- | A map of key-value pairs that specifies the tags to associate with the
    -- job.
    --
    -- A job can have a maximum of 50 tags. Each tag consists of a tag key and
    -- an associated tag value. The maximum length of a tag key is 128
    -- characters. The maximum length of a tag value is 256 characters.
    CreateClassificationJob -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The S3 buckets that contain the objects to analyze, and the scope of
    -- that analysis.
    CreateClassificationJob -> S3JobDefinition
s3JobDefinition :: S3JobDefinition,
    -- | The schedule for running the job. Valid values are:
    --
    -- -   ONE_TIME - Run the job only once. If you specify this value, don\'t
    --     specify a value for the scheduleFrequency property.
    --
    -- -   SCHEDULED - Run the job on a daily, weekly, or monthly basis. If you
    --     specify this value, use the scheduleFrequency property to define the
    --     recurrence pattern for the job.
    CreateClassificationJob -> JobType
jobType :: JobType,
    -- | A unique, case-sensitive token that you provide to ensure the
    -- idempotency of the request.
    CreateClassificationJob -> Text
clientToken :: Prelude.Text,
    -- | A custom name for the job. The name can contain as many as 500
    -- characters.
    CreateClassificationJob -> Text
name :: Prelude.Text
  }
  deriving (CreateClassificationJob -> CreateClassificationJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateClassificationJob -> CreateClassificationJob -> Bool
$c/= :: CreateClassificationJob -> CreateClassificationJob -> Bool
== :: CreateClassificationJob -> CreateClassificationJob -> Bool
$c== :: CreateClassificationJob -> CreateClassificationJob -> Bool
Prelude.Eq, ReadPrec [CreateClassificationJob]
ReadPrec CreateClassificationJob
Int -> ReadS CreateClassificationJob
ReadS [CreateClassificationJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateClassificationJob]
$creadListPrec :: ReadPrec [CreateClassificationJob]
readPrec :: ReadPrec CreateClassificationJob
$creadPrec :: ReadPrec CreateClassificationJob
readList :: ReadS [CreateClassificationJob]
$creadList :: ReadS [CreateClassificationJob]
readsPrec :: Int -> ReadS CreateClassificationJob
$creadsPrec :: Int -> ReadS CreateClassificationJob
Prelude.Read, Int -> CreateClassificationJob -> ShowS
[CreateClassificationJob] -> ShowS
CreateClassificationJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateClassificationJob] -> ShowS
$cshowList :: [CreateClassificationJob] -> ShowS
show :: CreateClassificationJob -> String
$cshow :: CreateClassificationJob -> String
showsPrec :: Int -> CreateClassificationJob -> ShowS
$cshowsPrec :: Int -> CreateClassificationJob -> ShowS
Prelude.Show, forall x. Rep CreateClassificationJob x -> CreateClassificationJob
forall x. CreateClassificationJob -> Rep CreateClassificationJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateClassificationJob x -> CreateClassificationJob
$cfrom :: forall x. CreateClassificationJob -> Rep CreateClassificationJob x
Prelude.Generic)

-- |
-- Create a value of 'CreateClassificationJob' 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:
--
-- 'allowListIds', 'createClassificationJob_allowListIds' - An array of unique identifiers, one for each allow list for the job to
-- use when it analyzes data.
--
-- 'customDataIdentifierIds', 'createClassificationJob_customDataIdentifierIds' - An array of unique identifiers, one for each custom data identifier for
-- the job to use when it analyzes data. To use only managed data
-- identifiers, don\'t specify a value for this property and specify a
-- value other than NONE for the managedDataIdentifierSelector property.
--
-- 'description', 'createClassificationJob_description' - A custom description of the job. The description can contain as many as
-- 200 characters.
--
-- 'initialRun', 'createClassificationJob_initialRun' - For a recurring job, specifies whether to analyze all existing, eligible
-- objects immediately after the job is created (true). To analyze only
-- those objects that are created or changed after you create the job and
-- before the job\'s first scheduled run, set this value to false.
--
-- If you configure the job to run only once, don\'t specify a value for
-- this property.
--
-- 'managedDataIdentifierIds', 'createClassificationJob_managedDataIdentifierIds' - An array of unique identifiers, one for each managed data identifier for
-- the job to include (use) or exclude (not use) when it analyzes data.
-- Inclusion or exclusion depends on the managed data identifier selection
-- type that you specify for the job (managedDataIdentifierSelector).
--
-- To retrieve a list of valid values for this property, use the
-- ListManagedDataIdentifiers operation.
--
-- 'managedDataIdentifierSelector', 'createClassificationJob_managedDataIdentifierSelector' - The selection type to apply when determining which managed data
-- identifiers the job uses to analyze data. Valid values are:
--
-- -   ALL - Use all the managed data identifiers that Amazon Macie
--     provides. If you specify this value, don\'t specify any values for
--     the managedDataIdentifierIds property.
--
-- -   EXCLUDE - Use all the managed data identifiers that Macie provides
--     except the managed data identifiers specified by the
--     managedDataIdentifierIds property.
--
-- -   INCLUDE - Use only the managed data identifiers specified by the
--     managedDataIdentifierIds property.
--
-- -   NONE - Don\'t use any managed data identifiers. If you specify this
--     value, specify at least one custom data identifier for the job
--     (customDataIdentifierIds) and don\'t specify any values for the
--     managedDataIdentifierIds property.
--
-- If you don\'t specify a value for this property, the job uses all
-- managed data identifiers. If you don\'t specify a value for this
-- property or you specify ALL or EXCLUDE for a recurring job, the job also
-- uses new managed data identifiers as they are released.
--
-- 'samplingPercentage', 'createClassificationJob_samplingPercentage' - The sampling depth, as a percentage, for the job to apply when
-- processing objects. This value determines the percentage of eligible
-- objects that the job analyzes. If this value is less than 100, Amazon
-- Macie selects the objects to analyze at random, up to the specified
-- percentage, and analyzes all the data in those objects.
--
-- 'scheduleFrequency', 'createClassificationJob_scheduleFrequency' - The recurrence pattern for running the job. To run the job only once,
-- don\'t specify a value for this property and set the value for the
-- jobType property to ONE_TIME.
--
-- 'tags', 'createClassificationJob_tags' - A map of key-value pairs that specifies the tags to associate with the
-- job.
--
-- A job can have a maximum of 50 tags. Each tag consists of a tag key and
-- an associated tag value. The maximum length of a tag key is 128
-- characters. The maximum length of a tag value is 256 characters.
--
-- 's3JobDefinition', 'createClassificationJob_s3JobDefinition' - The S3 buckets that contain the objects to analyze, and the scope of
-- that analysis.
--
-- 'jobType', 'createClassificationJob_jobType' - The schedule for running the job. Valid values are:
--
-- -   ONE_TIME - Run the job only once. If you specify this value, don\'t
--     specify a value for the scheduleFrequency property.
--
-- -   SCHEDULED - Run the job on a daily, weekly, or monthly basis. If you
--     specify this value, use the scheduleFrequency property to define the
--     recurrence pattern for the job.
--
-- 'clientToken', 'createClassificationJob_clientToken' - A unique, case-sensitive token that you provide to ensure the
-- idempotency of the request.
--
-- 'name', 'createClassificationJob_name' - A custom name for the job. The name can contain as many as 500
-- characters.
newCreateClassificationJob ::
  -- | 's3JobDefinition'
  S3JobDefinition ->
  -- | 'jobType'
  JobType ->
  -- | 'clientToken'
  Prelude.Text ->
  -- | 'name'
  Prelude.Text ->
  CreateClassificationJob
newCreateClassificationJob :: S3JobDefinition
-> JobType -> Text -> Text -> CreateClassificationJob
newCreateClassificationJob
  S3JobDefinition
pS3JobDefinition_
  JobType
pJobType_
  Text
pClientToken_
  Text
pName_ =
    CreateClassificationJob'
      { $sel:allowListIds:CreateClassificationJob' :: Maybe [Text]
allowListIds =
          forall a. Maybe a
Prelude.Nothing,
        $sel:customDataIdentifierIds:CreateClassificationJob' :: Maybe [Text]
customDataIdentifierIds = forall a. Maybe a
Prelude.Nothing,
        $sel:description:CreateClassificationJob' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
        $sel:initialRun:CreateClassificationJob' :: Maybe Bool
initialRun = forall a. Maybe a
Prelude.Nothing,
        $sel:managedDataIdentifierIds:CreateClassificationJob' :: Maybe [Text]
managedDataIdentifierIds = forall a. Maybe a
Prelude.Nothing,
        $sel:managedDataIdentifierSelector:CreateClassificationJob' :: Maybe ManagedDataIdentifierSelector
managedDataIdentifierSelector = forall a. Maybe a
Prelude.Nothing,
        $sel:samplingPercentage:CreateClassificationJob' :: Maybe Int
samplingPercentage = forall a. Maybe a
Prelude.Nothing,
        $sel:scheduleFrequency:CreateClassificationJob' :: Maybe JobScheduleFrequency
scheduleFrequency = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateClassificationJob' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:s3JobDefinition:CreateClassificationJob' :: S3JobDefinition
s3JobDefinition = S3JobDefinition
pS3JobDefinition_,
        $sel:jobType:CreateClassificationJob' :: JobType
jobType = JobType
pJobType_,
        $sel:clientToken:CreateClassificationJob' :: Text
clientToken = Text
pClientToken_,
        $sel:name:CreateClassificationJob' :: Text
name = Text
pName_
      }

-- | An array of unique identifiers, one for each allow list for the job to
-- use when it analyzes data.
createClassificationJob_allowListIds :: Lens.Lens' CreateClassificationJob (Prelude.Maybe [Prelude.Text])
createClassificationJob_allowListIds :: Lens' CreateClassificationJob (Maybe [Text])
createClassificationJob_allowListIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClassificationJob' {Maybe [Text]
allowListIds :: Maybe [Text]
$sel:allowListIds:CreateClassificationJob' :: CreateClassificationJob -> Maybe [Text]
allowListIds} -> Maybe [Text]
allowListIds) (\s :: CreateClassificationJob
s@CreateClassificationJob' {} Maybe [Text]
a -> CreateClassificationJob
s {$sel:allowListIds:CreateClassificationJob' :: Maybe [Text]
allowListIds = Maybe [Text]
a} :: CreateClassificationJob) 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 of unique identifiers, one for each custom data identifier for
-- the job to use when it analyzes data. To use only managed data
-- identifiers, don\'t specify a value for this property and specify a
-- value other than NONE for the managedDataIdentifierSelector property.
createClassificationJob_customDataIdentifierIds :: Lens.Lens' CreateClassificationJob (Prelude.Maybe [Prelude.Text])
createClassificationJob_customDataIdentifierIds :: Lens' CreateClassificationJob (Maybe [Text])
createClassificationJob_customDataIdentifierIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClassificationJob' {Maybe [Text]
customDataIdentifierIds :: Maybe [Text]
$sel:customDataIdentifierIds:CreateClassificationJob' :: CreateClassificationJob -> Maybe [Text]
customDataIdentifierIds} -> Maybe [Text]
customDataIdentifierIds) (\s :: CreateClassificationJob
s@CreateClassificationJob' {} Maybe [Text]
a -> CreateClassificationJob
s {$sel:customDataIdentifierIds:CreateClassificationJob' :: Maybe [Text]
customDataIdentifierIds = Maybe [Text]
a} :: CreateClassificationJob) 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 custom description of the job. The description can contain as many as
-- 200 characters.
createClassificationJob_description :: Lens.Lens' CreateClassificationJob (Prelude.Maybe Prelude.Text)
createClassificationJob_description :: Lens' CreateClassificationJob (Maybe Text)
createClassificationJob_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClassificationJob' {Maybe Text
description :: Maybe Text
$sel:description:CreateClassificationJob' :: CreateClassificationJob -> Maybe Text
description} -> Maybe Text
description) (\s :: CreateClassificationJob
s@CreateClassificationJob' {} Maybe Text
a -> CreateClassificationJob
s {$sel:description:CreateClassificationJob' :: Maybe Text
description = Maybe Text
a} :: CreateClassificationJob)

-- | For a recurring job, specifies whether to analyze all existing, eligible
-- objects immediately after the job is created (true). To analyze only
-- those objects that are created or changed after you create the job and
-- before the job\'s first scheduled run, set this value to false.
--
-- If you configure the job to run only once, don\'t specify a value for
-- this property.
createClassificationJob_initialRun :: Lens.Lens' CreateClassificationJob (Prelude.Maybe Prelude.Bool)
createClassificationJob_initialRun :: Lens' CreateClassificationJob (Maybe Bool)
createClassificationJob_initialRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClassificationJob' {Maybe Bool
initialRun :: Maybe Bool
$sel:initialRun:CreateClassificationJob' :: CreateClassificationJob -> Maybe Bool
initialRun} -> Maybe Bool
initialRun) (\s :: CreateClassificationJob
s@CreateClassificationJob' {} Maybe Bool
a -> CreateClassificationJob
s {$sel:initialRun:CreateClassificationJob' :: Maybe Bool
initialRun = Maybe Bool
a} :: CreateClassificationJob)

-- | An array of unique identifiers, one for each managed data identifier for
-- the job to include (use) or exclude (not use) when it analyzes data.
-- Inclusion or exclusion depends on the managed data identifier selection
-- type that you specify for the job (managedDataIdentifierSelector).
--
-- To retrieve a list of valid values for this property, use the
-- ListManagedDataIdentifiers operation.
createClassificationJob_managedDataIdentifierIds :: Lens.Lens' CreateClassificationJob (Prelude.Maybe [Prelude.Text])
createClassificationJob_managedDataIdentifierIds :: Lens' CreateClassificationJob (Maybe [Text])
createClassificationJob_managedDataIdentifierIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClassificationJob' {Maybe [Text]
managedDataIdentifierIds :: Maybe [Text]
$sel:managedDataIdentifierIds:CreateClassificationJob' :: CreateClassificationJob -> Maybe [Text]
managedDataIdentifierIds} -> Maybe [Text]
managedDataIdentifierIds) (\s :: CreateClassificationJob
s@CreateClassificationJob' {} Maybe [Text]
a -> CreateClassificationJob
s {$sel:managedDataIdentifierIds:CreateClassificationJob' :: Maybe [Text]
managedDataIdentifierIds = Maybe [Text]
a} :: CreateClassificationJob) 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 selection type to apply when determining which managed data
-- identifiers the job uses to analyze data. Valid values are:
--
-- -   ALL - Use all the managed data identifiers that Amazon Macie
--     provides. If you specify this value, don\'t specify any values for
--     the managedDataIdentifierIds property.
--
-- -   EXCLUDE - Use all the managed data identifiers that Macie provides
--     except the managed data identifiers specified by the
--     managedDataIdentifierIds property.
--
-- -   INCLUDE - Use only the managed data identifiers specified by the
--     managedDataIdentifierIds property.
--
-- -   NONE - Don\'t use any managed data identifiers. If you specify this
--     value, specify at least one custom data identifier for the job
--     (customDataIdentifierIds) and don\'t specify any values for the
--     managedDataIdentifierIds property.
--
-- If you don\'t specify a value for this property, the job uses all
-- managed data identifiers. If you don\'t specify a value for this
-- property or you specify ALL or EXCLUDE for a recurring job, the job also
-- uses new managed data identifiers as they are released.
createClassificationJob_managedDataIdentifierSelector :: Lens.Lens' CreateClassificationJob (Prelude.Maybe ManagedDataIdentifierSelector)
createClassificationJob_managedDataIdentifierSelector :: Lens' CreateClassificationJob (Maybe ManagedDataIdentifierSelector)
createClassificationJob_managedDataIdentifierSelector = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClassificationJob' {Maybe ManagedDataIdentifierSelector
managedDataIdentifierSelector :: Maybe ManagedDataIdentifierSelector
$sel:managedDataIdentifierSelector:CreateClassificationJob' :: CreateClassificationJob -> Maybe ManagedDataIdentifierSelector
managedDataIdentifierSelector} -> Maybe ManagedDataIdentifierSelector
managedDataIdentifierSelector) (\s :: CreateClassificationJob
s@CreateClassificationJob' {} Maybe ManagedDataIdentifierSelector
a -> CreateClassificationJob
s {$sel:managedDataIdentifierSelector:CreateClassificationJob' :: Maybe ManagedDataIdentifierSelector
managedDataIdentifierSelector = Maybe ManagedDataIdentifierSelector
a} :: CreateClassificationJob)

-- | The sampling depth, as a percentage, for the job to apply when
-- processing objects. This value determines the percentage of eligible
-- objects that the job analyzes. If this value is less than 100, Amazon
-- Macie selects the objects to analyze at random, up to the specified
-- percentage, and analyzes all the data in those objects.
createClassificationJob_samplingPercentage :: Lens.Lens' CreateClassificationJob (Prelude.Maybe Prelude.Int)
createClassificationJob_samplingPercentage :: Lens' CreateClassificationJob (Maybe Int)
createClassificationJob_samplingPercentage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClassificationJob' {Maybe Int
samplingPercentage :: Maybe Int
$sel:samplingPercentage:CreateClassificationJob' :: CreateClassificationJob -> Maybe Int
samplingPercentage} -> Maybe Int
samplingPercentage) (\s :: CreateClassificationJob
s@CreateClassificationJob' {} Maybe Int
a -> CreateClassificationJob
s {$sel:samplingPercentage:CreateClassificationJob' :: Maybe Int
samplingPercentage = Maybe Int
a} :: CreateClassificationJob)

-- | The recurrence pattern for running the job. To run the job only once,
-- don\'t specify a value for this property and set the value for the
-- jobType property to ONE_TIME.
createClassificationJob_scheduleFrequency :: Lens.Lens' CreateClassificationJob (Prelude.Maybe JobScheduleFrequency)
createClassificationJob_scheduleFrequency :: Lens' CreateClassificationJob (Maybe JobScheduleFrequency)
createClassificationJob_scheduleFrequency = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClassificationJob' {Maybe JobScheduleFrequency
scheduleFrequency :: Maybe JobScheduleFrequency
$sel:scheduleFrequency:CreateClassificationJob' :: CreateClassificationJob -> Maybe JobScheduleFrequency
scheduleFrequency} -> Maybe JobScheduleFrequency
scheduleFrequency) (\s :: CreateClassificationJob
s@CreateClassificationJob' {} Maybe JobScheduleFrequency
a -> CreateClassificationJob
s {$sel:scheduleFrequency:CreateClassificationJob' :: Maybe JobScheduleFrequency
scheduleFrequency = Maybe JobScheduleFrequency
a} :: CreateClassificationJob)

-- | A map of key-value pairs that specifies the tags to associate with the
-- job.
--
-- A job can have a maximum of 50 tags. Each tag consists of a tag key and
-- an associated tag value. The maximum length of a tag key is 128
-- characters. The maximum length of a tag value is 256 characters.
createClassificationJob_tags :: Lens.Lens' CreateClassificationJob (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createClassificationJob_tags :: Lens' CreateClassificationJob (Maybe (HashMap Text Text))
createClassificationJob_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClassificationJob' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateClassificationJob' :: CreateClassificationJob -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateClassificationJob
s@CreateClassificationJob' {} Maybe (HashMap Text Text)
a -> CreateClassificationJob
s {$sel:tags:CreateClassificationJob' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateClassificationJob) 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 S3 buckets that contain the objects to analyze, and the scope of
-- that analysis.
createClassificationJob_s3JobDefinition :: Lens.Lens' CreateClassificationJob S3JobDefinition
createClassificationJob_s3JobDefinition :: Lens' CreateClassificationJob S3JobDefinition
createClassificationJob_s3JobDefinition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClassificationJob' {S3JobDefinition
s3JobDefinition :: S3JobDefinition
$sel:s3JobDefinition:CreateClassificationJob' :: CreateClassificationJob -> S3JobDefinition
s3JobDefinition} -> S3JobDefinition
s3JobDefinition) (\s :: CreateClassificationJob
s@CreateClassificationJob' {} S3JobDefinition
a -> CreateClassificationJob
s {$sel:s3JobDefinition:CreateClassificationJob' :: S3JobDefinition
s3JobDefinition = S3JobDefinition
a} :: CreateClassificationJob)

-- | The schedule for running the job. Valid values are:
--
-- -   ONE_TIME - Run the job only once. If you specify this value, don\'t
--     specify a value for the scheduleFrequency property.
--
-- -   SCHEDULED - Run the job on a daily, weekly, or monthly basis. If you
--     specify this value, use the scheduleFrequency property to define the
--     recurrence pattern for the job.
createClassificationJob_jobType :: Lens.Lens' CreateClassificationJob JobType
createClassificationJob_jobType :: Lens' CreateClassificationJob JobType
createClassificationJob_jobType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClassificationJob' {JobType
jobType :: JobType
$sel:jobType:CreateClassificationJob' :: CreateClassificationJob -> JobType
jobType} -> JobType
jobType) (\s :: CreateClassificationJob
s@CreateClassificationJob' {} JobType
a -> CreateClassificationJob
s {$sel:jobType:CreateClassificationJob' :: JobType
jobType = JobType
a} :: CreateClassificationJob)

-- | A unique, case-sensitive token that you provide to ensure the
-- idempotency of the request.
createClassificationJob_clientToken :: Lens.Lens' CreateClassificationJob Prelude.Text
createClassificationJob_clientToken :: Lens' CreateClassificationJob Text
createClassificationJob_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClassificationJob' {Text
clientToken :: Text
$sel:clientToken:CreateClassificationJob' :: CreateClassificationJob -> Text
clientToken} -> Text
clientToken) (\s :: CreateClassificationJob
s@CreateClassificationJob' {} Text
a -> CreateClassificationJob
s {$sel:clientToken:CreateClassificationJob' :: Text
clientToken = Text
a} :: CreateClassificationJob)

-- | A custom name for the job. The name can contain as many as 500
-- characters.
createClassificationJob_name :: Lens.Lens' CreateClassificationJob Prelude.Text
createClassificationJob_name :: Lens' CreateClassificationJob Text
createClassificationJob_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClassificationJob' {Text
name :: Text
$sel:name:CreateClassificationJob' :: CreateClassificationJob -> Text
name} -> Text
name) (\s :: CreateClassificationJob
s@CreateClassificationJob' {} Text
a -> CreateClassificationJob
s {$sel:name:CreateClassificationJob' :: Text
name = Text
a} :: CreateClassificationJob)

instance Core.AWSRequest CreateClassificationJob where
  type
    AWSResponse CreateClassificationJob =
      CreateClassificationJobResponse
  request :: (Service -> Service)
-> CreateClassificationJob -> Request CreateClassificationJob
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateClassificationJob
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateClassificationJob)))
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 Text -> Int -> CreateClassificationJobResponse
CreateClassificationJobResponse'
            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
"jobArn")
            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
"jobId")
            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 CreateClassificationJob where
  hashWithSalt :: Int -> CreateClassificationJob -> Int
hashWithSalt Int
_salt CreateClassificationJob' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
Maybe ManagedDataIdentifierSelector
Maybe JobScheduleFrequency
Text
JobType
S3JobDefinition
name :: Text
clientToken :: Text
jobType :: JobType
s3JobDefinition :: S3JobDefinition
tags :: Maybe (HashMap Text Text)
scheduleFrequency :: Maybe JobScheduleFrequency
samplingPercentage :: Maybe Int
managedDataIdentifierSelector :: Maybe ManagedDataIdentifierSelector
managedDataIdentifierIds :: Maybe [Text]
initialRun :: Maybe Bool
description :: Maybe Text
customDataIdentifierIds :: Maybe [Text]
allowListIds :: Maybe [Text]
$sel:name:CreateClassificationJob' :: CreateClassificationJob -> Text
$sel:clientToken:CreateClassificationJob' :: CreateClassificationJob -> Text
$sel:jobType:CreateClassificationJob' :: CreateClassificationJob -> JobType
$sel:s3JobDefinition:CreateClassificationJob' :: CreateClassificationJob -> S3JobDefinition
$sel:tags:CreateClassificationJob' :: CreateClassificationJob -> Maybe (HashMap Text Text)
$sel:scheduleFrequency:CreateClassificationJob' :: CreateClassificationJob -> Maybe JobScheduleFrequency
$sel:samplingPercentage:CreateClassificationJob' :: CreateClassificationJob -> Maybe Int
$sel:managedDataIdentifierSelector:CreateClassificationJob' :: CreateClassificationJob -> Maybe ManagedDataIdentifierSelector
$sel:managedDataIdentifierIds:CreateClassificationJob' :: CreateClassificationJob -> Maybe [Text]
$sel:initialRun:CreateClassificationJob' :: CreateClassificationJob -> Maybe Bool
$sel:description:CreateClassificationJob' :: CreateClassificationJob -> Maybe Text
$sel:customDataIdentifierIds:CreateClassificationJob' :: CreateClassificationJob -> Maybe [Text]
$sel:allowListIds:CreateClassificationJob' :: CreateClassificationJob -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
allowListIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
customDataIdentifierIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
initialRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
managedDataIdentifierIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ManagedDataIdentifierSelector
managedDataIdentifierSelector
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
samplingPercentage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JobScheduleFrequency
scheduleFrequency
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` S3JobDefinition
s3JobDefinition
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` JobType
jobType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData CreateClassificationJob where
  rnf :: CreateClassificationJob -> ()
rnf CreateClassificationJob' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
Maybe ManagedDataIdentifierSelector
Maybe JobScheduleFrequency
Text
JobType
S3JobDefinition
name :: Text
clientToken :: Text
jobType :: JobType
s3JobDefinition :: S3JobDefinition
tags :: Maybe (HashMap Text Text)
scheduleFrequency :: Maybe JobScheduleFrequency
samplingPercentage :: Maybe Int
managedDataIdentifierSelector :: Maybe ManagedDataIdentifierSelector
managedDataIdentifierIds :: Maybe [Text]
initialRun :: Maybe Bool
description :: Maybe Text
customDataIdentifierIds :: Maybe [Text]
allowListIds :: Maybe [Text]
$sel:name:CreateClassificationJob' :: CreateClassificationJob -> Text
$sel:clientToken:CreateClassificationJob' :: CreateClassificationJob -> Text
$sel:jobType:CreateClassificationJob' :: CreateClassificationJob -> JobType
$sel:s3JobDefinition:CreateClassificationJob' :: CreateClassificationJob -> S3JobDefinition
$sel:tags:CreateClassificationJob' :: CreateClassificationJob -> Maybe (HashMap Text Text)
$sel:scheduleFrequency:CreateClassificationJob' :: CreateClassificationJob -> Maybe JobScheduleFrequency
$sel:samplingPercentage:CreateClassificationJob' :: CreateClassificationJob -> Maybe Int
$sel:managedDataIdentifierSelector:CreateClassificationJob' :: CreateClassificationJob -> Maybe ManagedDataIdentifierSelector
$sel:managedDataIdentifierIds:CreateClassificationJob' :: CreateClassificationJob -> Maybe [Text]
$sel:initialRun:CreateClassificationJob' :: CreateClassificationJob -> Maybe Bool
$sel:description:CreateClassificationJob' :: CreateClassificationJob -> Maybe Text
$sel:customDataIdentifierIds:CreateClassificationJob' :: CreateClassificationJob -> Maybe [Text]
$sel:allowListIds:CreateClassificationJob' :: CreateClassificationJob -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
allowListIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
customDataIdentifierIds
      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 Bool
initialRun
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
managedDataIdentifierIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ManagedDataIdentifierSelector
managedDataIdentifierSelector
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
samplingPercentage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JobScheduleFrequency
scheduleFrequency
      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 S3JobDefinition
s3JobDefinition
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf JobType
jobType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

instance Data.ToHeaders CreateClassificationJob where
  toHeaders :: CreateClassificationJob -> 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.ToJSON CreateClassificationJob where
  toJSON :: CreateClassificationJob -> Value
toJSON CreateClassificationJob' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
Maybe ManagedDataIdentifierSelector
Maybe JobScheduleFrequency
Text
JobType
S3JobDefinition
name :: Text
clientToken :: Text
jobType :: JobType
s3JobDefinition :: S3JobDefinition
tags :: Maybe (HashMap Text Text)
scheduleFrequency :: Maybe JobScheduleFrequency
samplingPercentage :: Maybe Int
managedDataIdentifierSelector :: Maybe ManagedDataIdentifierSelector
managedDataIdentifierIds :: Maybe [Text]
initialRun :: Maybe Bool
description :: Maybe Text
customDataIdentifierIds :: Maybe [Text]
allowListIds :: Maybe [Text]
$sel:name:CreateClassificationJob' :: CreateClassificationJob -> Text
$sel:clientToken:CreateClassificationJob' :: CreateClassificationJob -> Text
$sel:jobType:CreateClassificationJob' :: CreateClassificationJob -> JobType
$sel:s3JobDefinition:CreateClassificationJob' :: CreateClassificationJob -> S3JobDefinition
$sel:tags:CreateClassificationJob' :: CreateClassificationJob -> Maybe (HashMap Text Text)
$sel:scheduleFrequency:CreateClassificationJob' :: CreateClassificationJob -> Maybe JobScheduleFrequency
$sel:samplingPercentage:CreateClassificationJob' :: CreateClassificationJob -> Maybe Int
$sel:managedDataIdentifierSelector:CreateClassificationJob' :: CreateClassificationJob -> Maybe ManagedDataIdentifierSelector
$sel:managedDataIdentifierIds:CreateClassificationJob' :: CreateClassificationJob -> Maybe [Text]
$sel:initialRun:CreateClassificationJob' :: CreateClassificationJob -> Maybe Bool
$sel:description:CreateClassificationJob' :: CreateClassificationJob -> Maybe Text
$sel:customDataIdentifierIds:CreateClassificationJob' :: CreateClassificationJob -> Maybe [Text]
$sel:allowListIds:CreateClassificationJob' :: CreateClassificationJob -> Maybe [Text]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"allowListIds" 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]
allowListIds,
            (Key
"customDataIdentifierIds" 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]
customDataIdentifierIds,
            (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
"initialRun" 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 Bool
initialRun,
            (Key
"managedDataIdentifierIds" 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]
managedDataIdentifierIds,
            (Key
"managedDataIdentifierSelector" 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 ManagedDataIdentifierSelector
managedDataIdentifierSelector,
            (Key
"samplingPercentage" 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 Int
samplingPercentage,
            (Key
"scheduleFrequency" 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 JobScheduleFrequency
scheduleFrequency,
            (Key
"tags" 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 (HashMap Text Text)
tags,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"s3JobDefinition" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= S3JobDefinition
s3JobDefinition),
            forall a. a -> Maybe a
Prelude.Just (Key
"jobType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= JobType
jobType),
            forall a. a -> Maybe a
Prelude.Just (Key
"clientToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
clientToken),
            forall a. a -> Maybe a
Prelude.Just (Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)
          ]
      )

instance Data.ToPath CreateClassificationJob where
  toPath :: CreateClassificationJob -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/jobs"

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

-- | /See:/ 'newCreateClassificationJobResponse' smart constructor.
data CreateClassificationJobResponse = CreateClassificationJobResponse'
  { -- | The Amazon Resource Name (ARN) of the job.
    CreateClassificationJobResponse -> Maybe Text
jobArn :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier for the job.
    CreateClassificationJobResponse -> Maybe Text
jobId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateClassificationJobResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateClassificationJobResponse
-> CreateClassificationJobResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateClassificationJobResponse
-> CreateClassificationJobResponse -> Bool
$c/= :: CreateClassificationJobResponse
-> CreateClassificationJobResponse -> Bool
== :: CreateClassificationJobResponse
-> CreateClassificationJobResponse -> Bool
$c== :: CreateClassificationJobResponse
-> CreateClassificationJobResponse -> Bool
Prelude.Eq, ReadPrec [CreateClassificationJobResponse]
ReadPrec CreateClassificationJobResponse
Int -> ReadS CreateClassificationJobResponse
ReadS [CreateClassificationJobResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateClassificationJobResponse]
$creadListPrec :: ReadPrec [CreateClassificationJobResponse]
readPrec :: ReadPrec CreateClassificationJobResponse
$creadPrec :: ReadPrec CreateClassificationJobResponse
readList :: ReadS [CreateClassificationJobResponse]
$creadList :: ReadS [CreateClassificationJobResponse]
readsPrec :: Int -> ReadS CreateClassificationJobResponse
$creadsPrec :: Int -> ReadS CreateClassificationJobResponse
Prelude.Read, Int -> CreateClassificationJobResponse -> ShowS
[CreateClassificationJobResponse] -> ShowS
CreateClassificationJobResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateClassificationJobResponse] -> ShowS
$cshowList :: [CreateClassificationJobResponse] -> ShowS
show :: CreateClassificationJobResponse -> String
$cshow :: CreateClassificationJobResponse -> String
showsPrec :: Int -> CreateClassificationJobResponse -> ShowS
$cshowsPrec :: Int -> CreateClassificationJobResponse -> ShowS
Prelude.Show, forall x.
Rep CreateClassificationJobResponse x
-> CreateClassificationJobResponse
forall x.
CreateClassificationJobResponse
-> Rep CreateClassificationJobResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateClassificationJobResponse x
-> CreateClassificationJobResponse
$cfrom :: forall x.
CreateClassificationJobResponse
-> Rep CreateClassificationJobResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateClassificationJobResponse' 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:
--
-- 'jobArn', 'createClassificationJobResponse_jobArn' - The Amazon Resource Name (ARN) of the job.
--
-- 'jobId', 'createClassificationJobResponse_jobId' - The unique identifier for the job.
--
-- 'httpStatus', 'createClassificationJobResponse_httpStatus' - The response's http status code.
newCreateClassificationJobResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateClassificationJobResponse
newCreateClassificationJobResponse :: Int -> CreateClassificationJobResponse
newCreateClassificationJobResponse Int
pHttpStatus_ =
  CreateClassificationJobResponse'
    { $sel:jobArn:CreateClassificationJobResponse' :: Maybe Text
jobArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:jobId:CreateClassificationJobResponse' :: Maybe Text
jobId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateClassificationJobResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the job.
createClassificationJobResponse_jobArn :: Lens.Lens' CreateClassificationJobResponse (Prelude.Maybe Prelude.Text)
createClassificationJobResponse_jobArn :: Lens' CreateClassificationJobResponse (Maybe Text)
createClassificationJobResponse_jobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClassificationJobResponse' {Maybe Text
jobArn :: Maybe Text
$sel:jobArn:CreateClassificationJobResponse' :: CreateClassificationJobResponse -> Maybe Text
jobArn} -> Maybe Text
jobArn) (\s :: CreateClassificationJobResponse
s@CreateClassificationJobResponse' {} Maybe Text
a -> CreateClassificationJobResponse
s {$sel:jobArn:CreateClassificationJobResponse' :: Maybe Text
jobArn = Maybe Text
a} :: CreateClassificationJobResponse)

-- | The unique identifier for the job.
createClassificationJobResponse_jobId :: Lens.Lens' CreateClassificationJobResponse (Prelude.Maybe Prelude.Text)
createClassificationJobResponse_jobId :: Lens' CreateClassificationJobResponse (Maybe Text)
createClassificationJobResponse_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClassificationJobResponse' {Maybe Text
jobId :: Maybe Text
$sel:jobId:CreateClassificationJobResponse' :: CreateClassificationJobResponse -> Maybe Text
jobId} -> Maybe Text
jobId) (\s :: CreateClassificationJobResponse
s@CreateClassificationJobResponse' {} Maybe Text
a -> CreateClassificationJobResponse
s {$sel:jobId:CreateClassificationJobResponse' :: Maybe Text
jobId = Maybe Text
a} :: CreateClassificationJobResponse)

-- | The response's http status code.
createClassificationJobResponse_httpStatus :: Lens.Lens' CreateClassificationJobResponse Prelude.Int
createClassificationJobResponse_httpStatus :: Lens' CreateClassificationJobResponse Int
createClassificationJobResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClassificationJobResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateClassificationJobResponse' :: CreateClassificationJobResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CreateClassificationJobResponse
s@CreateClassificationJobResponse' {} Int
a -> CreateClassificationJobResponse
s {$sel:httpStatus:CreateClassificationJobResponse' :: Int
httpStatus = Int
a} :: CreateClassificationJobResponse)

instance
  Prelude.NFData
    CreateClassificationJobResponse
  where
  rnf :: CreateClassificationJobResponse -> ()
rnf CreateClassificationJobResponse' {Int
Maybe Text
httpStatus :: Int
jobId :: Maybe Text
jobArn :: Maybe Text
$sel:httpStatus:CreateClassificationJobResponse' :: CreateClassificationJobResponse -> Int
$sel:jobId:CreateClassificationJobResponse' :: CreateClassificationJobResponse -> Maybe Text
$sel:jobArn:CreateClassificationJobResponse' :: CreateClassificationJobResponse -> Maybe Text
..} =
    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 Int
httpStatus