{-# 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.SageMakerGeoSpatial.StartVectorEnrichmentJob
-- 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 a Vector Enrichment job for the supplied job type. Currently,
-- there are two supported job types: reverse geocoding and map matching.
module Amazonka.SageMakerGeoSpatial.StartVectorEnrichmentJob
  ( -- * Creating a Request
    StartVectorEnrichmentJob (..),
    newStartVectorEnrichmentJob,

    -- * Request Lenses
    startVectorEnrichmentJob_clientToken,
    startVectorEnrichmentJob_kmsKeyId,
    startVectorEnrichmentJob_tags,
    startVectorEnrichmentJob_executionRoleArn,
    startVectorEnrichmentJob_inputConfig,
    startVectorEnrichmentJob_jobConfig,
    startVectorEnrichmentJob_name,

    -- * Destructuring the Response
    StartVectorEnrichmentJobResponse (..),
    newStartVectorEnrichmentJobResponse,

    -- * Response Lenses
    startVectorEnrichmentJobResponse_kmsKeyId,
    startVectorEnrichmentJobResponse_tags,
    startVectorEnrichmentJobResponse_httpStatus,
    startVectorEnrichmentJobResponse_arn,
    startVectorEnrichmentJobResponse_creationTime,
    startVectorEnrichmentJobResponse_durationInSeconds,
    startVectorEnrichmentJobResponse_executionRoleArn,
    startVectorEnrichmentJobResponse_inputConfig,
    startVectorEnrichmentJobResponse_jobConfig,
    startVectorEnrichmentJobResponse_name,
    startVectorEnrichmentJobResponse_status,
    startVectorEnrichmentJobResponse_type,
  )
where

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
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.SageMakerGeoSpatial.Types

-- | /See:/ 'newStartVectorEnrichmentJob' smart constructor.
data StartVectorEnrichmentJob = StartVectorEnrichmentJob'
  { -- | A unique token that guarantees that the call to this API is idempotent.
    StartVectorEnrichmentJob -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Key Management Service (KMS) key ID for server-side
    -- encryption.
    StartVectorEnrichmentJob -> Maybe Text
kmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | Each tag consists of a key and a value.
    StartVectorEnrichmentJob -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The Amazon Resource Name (ARN) of the IAM role that you specified for
    -- the job.
    StartVectorEnrichmentJob -> Text
executionRoleArn :: Prelude.Text,
    -- | Input configuration information for the Vector Enrichment job.
    StartVectorEnrichmentJob -> VectorEnrichmentJobInputConfig
inputConfig :: VectorEnrichmentJobInputConfig,
    -- | An object containing information about the job configuration.
    StartVectorEnrichmentJob -> VectorEnrichmentJobConfig
jobConfig :: VectorEnrichmentJobConfig,
    -- | The name of the Vector Enrichment job.
    StartVectorEnrichmentJob -> Text
name :: Prelude.Text
  }
  deriving (StartVectorEnrichmentJob -> StartVectorEnrichmentJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartVectorEnrichmentJob -> StartVectorEnrichmentJob -> Bool
$c/= :: StartVectorEnrichmentJob -> StartVectorEnrichmentJob -> Bool
== :: StartVectorEnrichmentJob -> StartVectorEnrichmentJob -> Bool
$c== :: StartVectorEnrichmentJob -> StartVectorEnrichmentJob -> Bool
Prelude.Eq, ReadPrec [StartVectorEnrichmentJob]
ReadPrec StartVectorEnrichmentJob
Int -> ReadS StartVectorEnrichmentJob
ReadS [StartVectorEnrichmentJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartVectorEnrichmentJob]
$creadListPrec :: ReadPrec [StartVectorEnrichmentJob]
readPrec :: ReadPrec StartVectorEnrichmentJob
$creadPrec :: ReadPrec StartVectorEnrichmentJob
readList :: ReadS [StartVectorEnrichmentJob]
$creadList :: ReadS [StartVectorEnrichmentJob]
readsPrec :: Int -> ReadS StartVectorEnrichmentJob
$creadsPrec :: Int -> ReadS StartVectorEnrichmentJob
Prelude.Read, Int -> StartVectorEnrichmentJob -> ShowS
[StartVectorEnrichmentJob] -> ShowS
StartVectorEnrichmentJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartVectorEnrichmentJob] -> ShowS
$cshowList :: [StartVectorEnrichmentJob] -> ShowS
show :: StartVectorEnrichmentJob -> String
$cshow :: StartVectorEnrichmentJob -> String
showsPrec :: Int -> StartVectorEnrichmentJob -> ShowS
$cshowsPrec :: Int -> StartVectorEnrichmentJob -> ShowS
Prelude.Show, forall x.
Rep StartVectorEnrichmentJob x -> StartVectorEnrichmentJob
forall x.
StartVectorEnrichmentJob -> Rep StartVectorEnrichmentJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StartVectorEnrichmentJob x -> StartVectorEnrichmentJob
$cfrom :: forall x.
StartVectorEnrichmentJob -> Rep StartVectorEnrichmentJob x
Prelude.Generic)

-- |
-- Create a value of 'StartVectorEnrichmentJob' 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:
--
-- 'clientToken', 'startVectorEnrichmentJob_clientToken' - A unique token that guarantees that the call to this API is idempotent.
--
-- 'kmsKeyId', 'startVectorEnrichmentJob_kmsKeyId' - The Amazon Key Management Service (KMS) key ID for server-side
-- encryption.
--
-- 'tags', 'startVectorEnrichmentJob_tags' - Each tag consists of a key and a value.
--
-- 'executionRoleArn', 'startVectorEnrichmentJob_executionRoleArn' - The Amazon Resource Name (ARN) of the IAM role that you specified for
-- the job.
--
-- 'inputConfig', 'startVectorEnrichmentJob_inputConfig' - Input configuration information for the Vector Enrichment job.
--
-- 'jobConfig', 'startVectorEnrichmentJob_jobConfig' - An object containing information about the job configuration.
--
-- 'name', 'startVectorEnrichmentJob_name' - The name of the Vector Enrichment job.
newStartVectorEnrichmentJob ::
  -- | 'executionRoleArn'
  Prelude.Text ->
  -- | 'inputConfig'
  VectorEnrichmentJobInputConfig ->
  -- | 'jobConfig'
  VectorEnrichmentJobConfig ->
  -- | 'name'
  Prelude.Text ->
  StartVectorEnrichmentJob
newStartVectorEnrichmentJob :: Text
-> VectorEnrichmentJobInputConfig
-> VectorEnrichmentJobConfig
-> Text
-> StartVectorEnrichmentJob
newStartVectorEnrichmentJob
  Text
pExecutionRoleArn_
  VectorEnrichmentJobInputConfig
pInputConfig_
  VectorEnrichmentJobConfig
pJobConfig_
  Text
pName_ =
    StartVectorEnrichmentJob'
      { $sel:clientToken:StartVectorEnrichmentJob' :: Maybe Text
clientToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:kmsKeyId:StartVectorEnrichmentJob' :: Maybe Text
kmsKeyId = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:StartVectorEnrichmentJob' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:executionRoleArn:StartVectorEnrichmentJob' :: Text
executionRoleArn = Text
pExecutionRoleArn_,
        $sel:inputConfig:StartVectorEnrichmentJob' :: VectorEnrichmentJobInputConfig
inputConfig = VectorEnrichmentJobInputConfig
pInputConfig_,
        $sel:jobConfig:StartVectorEnrichmentJob' :: VectorEnrichmentJobConfig
jobConfig = VectorEnrichmentJobConfig
pJobConfig_,
        $sel:name:StartVectorEnrichmentJob' :: Text
name = Text
pName_
      }

-- | A unique token that guarantees that the call to this API is idempotent.
startVectorEnrichmentJob_clientToken :: Lens.Lens' StartVectorEnrichmentJob (Prelude.Maybe Prelude.Text)
startVectorEnrichmentJob_clientToken :: Lens' StartVectorEnrichmentJob (Maybe Text)
startVectorEnrichmentJob_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartVectorEnrichmentJob' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: StartVectorEnrichmentJob
s@StartVectorEnrichmentJob' {} Maybe Text
a -> StartVectorEnrichmentJob
s {$sel:clientToken:StartVectorEnrichmentJob' :: Maybe Text
clientToken = Maybe Text
a} :: StartVectorEnrichmentJob)

-- | The Amazon Key Management Service (KMS) key ID for server-side
-- encryption.
startVectorEnrichmentJob_kmsKeyId :: Lens.Lens' StartVectorEnrichmentJob (Prelude.Maybe Prelude.Text)
startVectorEnrichmentJob_kmsKeyId :: Lens' StartVectorEnrichmentJob (Maybe Text)
startVectorEnrichmentJob_kmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartVectorEnrichmentJob' {Maybe Text
kmsKeyId :: Maybe Text
$sel:kmsKeyId:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> Maybe Text
kmsKeyId} -> Maybe Text
kmsKeyId) (\s :: StartVectorEnrichmentJob
s@StartVectorEnrichmentJob' {} Maybe Text
a -> StartVectorEnrichmentJob
s {$sel:kmsKeyId:StartVectorEnrichmentJob' :: Maybe Text
kmsKeyId = Maybe Text
a} :: StartVectorEnrichmentJob)

-- | Each tag consists of a key and a value.
startVectorEnrichmentJob_tags :: Lens.Lens' StartVectorEnrichmentJob (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
startVectorEnrichmentJob_tags :: Lens' StartVectorEnrichmentJob (Maybe (HashMap Text Text))
startVectorEnrichmentJob_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartVectorEnrichmentJob' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: StartVectorEnrichmentJob
s@StartVectorEnrichmentJob' {} Maybe (HashMap Text Text)
a -> StartVectorEnrichmentJob
s {$sel:tags:StartVectorEnrichmentJob' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: StartVectorEnrichmentJob) 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 Amazon Resource Name (ARN) of the IAM role that you specified for
-- the job.
startVectorEnrichmentJob_executionRoleArn :: Lens.Lens' StartVectorEnrichmentJob Prelude.Text
startVectorEnrichmentJob_executionRoleArn :: Lens' StartVectorEnrichmentJob Text
startVectorEnrichmentJob_executionRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartVectorEnrichmentJob' {Text
executionRoleArn :: Text
$sel:executionRoleArn:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> Text
executionRoleArn} -> Text
executionRoleArn) (\s :: StartVectorEnrichmentJob
s@StartVectorEnrichmentJob' {} Text
a -> StartVectorEnrichmentJob
s {$sel:executionRoleArn:StartVectorEnrichmentJob' :: Text
executionRoleArn = Text
a} :: StartVectorEnrichmentJob)

-- | Input configuration information for the Vector Enrichment job.
startVectorEnrichmentJob_inputConfig :: Lens.Lens' StartVectorEnrichmentJob VectorEnrichmentJobInputConfig
startVectorEnrichmentJob_inputConfig :: Lens' StartVectorEnrichmentJob VectorEnrichmentJobInputConfig
startVectorEnrichmentJob_inputConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartVectorEnrichmentJob' {VectorEnrichmentJobInputConfig
inputConfig :: VectorEnrichmentJobInputConfig
$sel:inputConfig:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> VectorEnrichmentJobInputConfig
inputConfig} -> VectorEnrichmentJobInputConfig
inputConfig) (\s :: StartVectorEnrichmentJob
s@StartVectorEnrichmentJob' {} VectorEnrichmentJobInputConfig
a -> StartVectorEnrichmentJob
s {$sel:inputConfig:StartVectorEnrichmentJob' :: VectorEnrichmentJobInputConfig
inputConfig = VectorEnrichmentJobInputConfig
a} :: StartVectorEnrichmentJob)

-- | An object containing information about the job configuration.
startVectorEnrichmentJob_jobConfig :: Lens.Lens' StartVectorEnrichmentJob VectorEnrichmentJobConfig
startVectorEnrichmentJob_jobConfig :: Lens' StartVectorEnrichmentJob VectorEnrichmentJobConfig
startVectorEnrichmentJob_jobConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartVectorEnrichmentJob' {VectorEnrichmentJobConfig
jobConfig :: VectorEnrichmentJobConfig
$sel:jobConfig:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> VectorEnrichmentJobConfig
jobConfig} -> VectorEnrichmentJobConfig
jobConfig) (\s :: StartVectorEnrichmentJob
s@StartVectorEnrichmentJob' {} VectorEnrichmentJobConfig
a -> StartVectorEnrichmentJob
s {$sel:jobConfig:StartVectorEnrichmentJob' :: VectorEnrichmentJobConfig
jobConfig = VectorEnrichmentJobConfig
a} :: StartVectorEnrichmentJob)

-- | The name of the Vector Enrichment job.
startVectorEnrichmentJob_name :: Lens.Lens' StartVectorEnrichmentJob Prelude.Text
startVectorEnrichmentJob_name :: Lens' StartVectorEnrichmentJob Text
startVectorEnrichmentJob_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartVectorEnrichmentJob' {Text
name :: Text
$sel:name:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> Text
name} -> Text
name) (\s :: StartVectorEnrichmentJob
s@StartVectorEnrichmentJob' {} Text
a -> StartVectorEnrichmentJob
s {$sel:name:StartVectorEnrichmentJob' :: Text
name = Text
a} :: StartVectorEnrichmentJob)

instance Core.AWSRequest StartVectorEnrichmentJob where
  type
    AWSResponse StartVectorEnrichmentJob =
      StartVectorEnrichmentJobResponse
  request :: (Service -> Service)
-> StartVectorEnrichmentJob -> Request StartVectorEnrichmentJob
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 StartVectorEnrichmentJob
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StartVectorEnrichmentJob)))
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 (HashMap Text Text)
-> Int
-> Text
-> POSIX
-> Int
-> Text
-> VectorEnrichmentJobInputConfig
-> VectorEnrichmentJobConfig
-> Text
-> VectorEnrichmentJobStatus
-> VectorEnrichmentJobType
-> StartVectorEnrichmentJobResponse
StartVectorEnrichmentJobResponse'
            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
"KmsKeyId")
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String 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 a
Data..:> Key
"CreationTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"DurationInSeconds")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"ExecutionRoleArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"InputConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"JobConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String 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 a
Data..:> Key
"Status")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"Type")
      )

instance Prelude.Hashable StartVectorEnrichmentJob where
  hashWithSalt :: Int -> StartVectorEnrichmentJob -> Int
hashWithSalt Int
_salt StartVectorEnrichmentJob' {Maybe Text
Maybe (HashMap Text Text)
Text
VectorEnrichmentJobConfig
VectorEnrichmentJobInputConfig
name :: Text
jobConfig :: VectorEnrichmentJobConfig
inputConfig :: VectorEnrichmentJobInputConfig
executionRoleArn :: Text
tags :: Maybe (HashMap Text Text)
kmsKeyId :: Maybe Text
clientToken :: Maybe Text
$sel:name:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> Text
$sel:jobConfig:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> VectorEnrichmentJobConfig
$sel:inputConfig:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> VectorEnrichmentJobInputConfig
$sel:executionRoleArn:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> Text
$sel:tags:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> Maybe (HashMap Text Text)
$sel:kmsKeyId:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> Maybe Text
$sel:clientToken:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
kmsKeyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
executionRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` VectorEnrichmentJobInputConfig
inputConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` VectorEnrichmentJobConfig
jobConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData StartVectorEnrichmentJob where
  rnf :: StartVectorEnrichmentJob -> ()
rnf StartVectorEnrichmentJob' {Maybe Text
Maybe (HashMap Text Text)
Text
VectorEnrichmentJobConfig
VectorEnrichmentJobInputConfig
name :: Text
jobConfig :: VectorEnrichmentJobConfig
inputConfig :: VectorEnrichmentJobInputConfig
executionRoleArn :: Text
tags :: Maybe (HashMap Text Text)
kmsKeyId :: Maybe Text
clientToken :: Maybe Text
$sel:name:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> Text
$sel:jobConfig:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> VectorEnrichmentJobConfig
$sel:inputConfig:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> VectorEnrichmentJobInputConfig
$sel:executionRoleArn:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> Text
$sel:tags:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> Maybe (HashMap Text Text)
$sel:kmsKeyId:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> Maybe Text
$sel:clientToken:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kmsKeyId
      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 Text
executionRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf VectorEnrichmentJobInputConfig
inputConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf VectorEnrichmentJobConfig
jobConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

instance Data.ToHeaders StartVectorEnrichmentJob where
  toHeaders :: StartVectorEnrichmentJob -> 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 StartVectorEnrichmentJob where
  toJSON :: StartVectorEnrichmentJob -> Value
toJSON StartVectorEnrichmentJob' {Maybe Text
Maybe (HashMap Text Text)
Text
VectorEnrichmentJobConfig
VectorEnrichmentJobInputConfig
name :: Text
jobConfig :: VectorEnrichmentJobConfig
inputConfig :: VectorEnrichmentJobInputConfig
executionRoleArn :: Text
tags :: Maybe (HashMap Text Text)
kmsKeyId :: Maybe Text
clientToken :: Maybe Text
$sel:name:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> Text
$sel:jobConfig:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> VectorEnrichmentJobConfig
$sel:inputConfig:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> VectorEnrichmentJobInputConfig
$sel:executionRoleArn:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> Text
$sel:tags:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> Maybe (HashMap Text Text)
$sel:kmsKeyId:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> Maybe Text
$sel:clientToken:StartVectorEnrichmentJob' :: StartVectorEnrichmentJob -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ClientToken" 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
clientToken,
            (Key
"KmsKeyId" 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
kmsKeyId,
            (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
"ExecutionRoleArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
executionRoleArn),
            forall a. a -> Maybe a
Prelude.Just (Key
"InputConfig" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= VectorEnrichmentJobInputConfig
inputConfig),
            forall a. a -> Maybe a
Prelude.Just (Key
"JobConfig" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= VectorEnrichmentJobConfig
jobConfig),
            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 StartVectorEnrichmentJob where
  toPath :: StartVectorEnrichmentJob -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/vector-enrichment-jobs"

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

-- | /See:/ 'newStartVectorEnrichmentJobResponse' smart constructor.
data StartVectorEnrichmentJobResponse = StartVectorEnrichmentJobResponse'
  { -- | The Amazon Key Management Service (KMS) key ID for server-side
    -- encryption.
    StartVectorEnrichmentJobResponse -> Maybe Text
kmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | Each tag consists of a key and a value.
    StartVectorEnrichmentJobResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The response's http status code.
    StartVectorEnrichmentJobResponse -> Int
httpStatus :: Prelude.Int,
    -- | The Amazon Resource Name (ARN) of the Vector Enrichment job.
    StartVectorEnrichmentJobResponse -> Text
arn :: Prelude.Text,
    -- | The creation time.
    StartVectorEnrichmentJobResponse -> POSIX
creationTime :: Data.POSIX,
    -- | The duration of the Vector Enrichment job, in seconds.
    StartVectorEnrichmentJobResponse -> Int
durationInSeconds :: Prelude.Int,
    -- | The Amazon Resource Name (ARN) of the IAM role that you specified for
    -- the job.
    StartVectorEnrichmentJobResponse -> Text
executionRoleArn :: Prelude.Text,
    -- | Input configuration information for starting the Vector Enrichment job.
    StartVectorEnrichmentJobResponse -> VectorEnrichmentJobInputConfig
inputConfig :: VectorEnrichmentJobInputConfig,
    -- | An object containing information about the job configuration.
    StartVectorEnrichmentJobResponse -> VectorEnrichmentJobConfig
jobConfig :: VectorEnrichmentJobConfig,
    -- | The name of the Vector Enrichment job.
    StartVectorEnrichmentJobResponse -> Text
name :: Prelude.Text,
    -- | The status of the Vector Enrichment job being started.
    StartVectorEnrichmentJobResponse -> VectorEnrichmentJobStatus
status :: VectorEnrichmentJobStatus,
    -- | The type of the Vector Enrichment job.
    StartVectorEnrichmentJobResponse -> VectorEnrichmentJobType
type' :: VectorEnrichmentJobType
  }
  deriving (StartVectorEnrichmentJobResponse
-> StartVectorEnrichmentJobResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartVectorEnrichmentJobResponse
-> StartVectorEnrichmentJobResponse -> Bool
$c/= :: StartVectorEnrichmentJobResponse
-> StartVectorEnrichmentJobResponse -> Bool
== :: StartVectorEnrichmentJobResponse
-> StartVectorEnrichmentJobResponse -> Bool
$c== :: StartVectorEnrichmentJobResponse
-> StartVectorEnrichmentJobResponse -> Bool
Prelude.Eq, ReadPrec [StartVectorEnrichmentJobResponse]
ReadPrec StartVectorEnrichmentJobResponse
Int -> ReadS StartVectorEnrichmentJobResponse
ReadS [StartVectorEnrichmentJobResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartVectorEnrichmentJobResponse]
$creadListPrec :: ReadPrec [StartVectorEnrichmentJobResponse]
readPrec :: ReadPrec StartVectorEnrichmentJobResponse
$creadPrec :: ReadPrec StartVectorEnrichmentJobResponse
readList :: ReadS [StartVectorEnrichmentJobResponse]
$creadList :: ReadS [StartVectorEnrichmentJobResponse]
readsPrec :: Int -> ReadS StartVectorEnrichmentJobResponse
$creadsPrec :: Int -> ReadS StartVectorEnrichmentJobResponse
Prelude.Read, Int -> StartVectorEnrichmentJobResponse -> ShowS
[StartVectorEnrichmentJobResponse] -> ShowS
StartVectorEnrichmentJobResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartVectorEnrichmentJobResponse] -> ShowS
$cshowList :: [StartVectorEnrichmentJobResponse] -> ShowS
show :: StartVectorEnrichmentJobResponse -> String
$cshow :: StartVectorEnrichmentJobResponse -> String
showsPrec :: Int -> StartVectorEnrichmentJobResponse -> ShowS
$cshowsPrec :: Int -> StartVectorEnrichmentJobResponse -> ShowS
Prelude.Show, forall x.
Rep StartVectorEnrichmentJobResponse x
-> StartVectorEnrichmentJobResponse
forall x.
StartVectorEnrichmentJobResponse
-> Rep StartVectorEnrichmentJobResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StartVectorEnrichmentJobResponse x
-> StartVectorEnrichmentJobResponse
$cfrom :: forall x.
StartVectorEnrichmentJobResponse
-> Rep StartVectorEnrichmentJobResponse x
Prelude.Generic)

-- |
-- Create a value of 'StartVectorEnrichmentJobResponse' 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:
--
-- 'kmsKeyId', 'startVectorEnrichmentJobResponse_kmsKeyId' - The Amazon Key Management Service (KMS) key ID for server-side
-- encryption.
--
-- 'tags', 'startVectorEnrichmentJobResponse_tags' - Each tag consists of a key and a value.
--
-- 'httpStatus', 'startVectorEnrichmentJobResponse_httpStatus' - The response's http status code.
--
-- 'arn', 'startVectorEnrichmentJobResponse_arn' - The Amazon Resource Name (ARN) of the Vector Enrichment job.
--
-- 'creationTime', 'startVectorEnrichmentJobResponse_creationTime' - The creation time.
--
-- 'durationInSeconds', 'startVectorEnrichmentJobResponse_durationInSeconds' - The duration of the Vector Enrichment job, in seconds.
--
-- 'executionRoleArn', 'startVectorEnrichmentJobResponse_executionRoleArn' - The Amazon Resource Name (ARN) of the IAM role that you specified for
-- the job.
--
-- 'inputConfig', 'startVectorEnrichmentJobResponse_inputConfig' - Input configuration information for starting the Vector Enrichment job.
--
-- 'jobConfig', 'startVectorEnrichmentJobResponse_jobConfig' - An object containing information about the job configuration.
--
-- 'name', 'startVectorEnrichmentJobResponse_name' - The name of the Vector Enrichment job.
--
-- 'status', 'startVectorEnrichmentJobResponse_status' - The status of the Vector Enrichment job being started.
--
-- 'type'', 'startVectorEnrichmentJobResponse_type' - The type of the Vector Enrichment job.
newStartVectorEnrichmentJobResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'arn'
  Prelude.Text ->
  -- | 'creationTime'
  Prelude.UTCTime ->
  -- | 'durationInSeconds'
  Prelude.Int ->
  -- | 'executionRoleArn'
  Prelude.Text ->
  -- | 'inputConfig'
  VectorEnrichmentJobInputConfig ->
  -- | 'jobConfig'
  VectorEnrichmentJobConfig ->
  -- | 'name'
  Prelude.Text ->
  -- | 'status'
  VectorEnrichmentJobStatus ->
  -- | 'type''
  VectorEnrichmentJobType ->
  StartVectorEnrichmentJobResponse
newStartVectorEnrichmentJobResponse :: Int
-> Text
-> UTCTime
-> Int
-> Text
-> VectorEnrichmentJobInputConfig
-> VectorEnrichmentJobConfig
-> Text
-> VectorEnrichmentJobStatus
-> VectorEnrichmentJobType
-> StartVectorEnrichmentJobResponse
newStartVectorEnrichmentJobResponse
  Int
pHttpStatus_
  Text
pArn_
  UTCTime
pCreationTime_
  Int
pDurationInSeconds_
  Text
pExecutionRoleArn_
  VectorEnrichmentJobInputConfig
pInputConfig_
  VectorEnrichmentJobConfig
pJobConfig_
  Text
pName_
  VectorEnrichmentJobStatus
pStatus_
  VectorEnrichmentJobType
pType_ =
    StartVectorEnrichmentJobResponse'
      { $sel:kmsKeyId:StartVectorEnrichmentJobResponse' :: Maybe Text
kmsKeyId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:tags:StartVectorEnrichmentJobResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:StartVectorEnrichmentJobResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:arn:StartVectorEnrichmentJobResponse' :: Text
arn = Text
pArn_,
        $sel:creationTime:StartVectorEnrichmentJobResponse' :: POSIX
creationTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationTime_,
        $sel:durationInSeconds:StartVectorEnrichmentJobResponse' :: Int
durationInSeconds = Int
pDurationInSeconds_,
        $sel:executionRoleArn:StartVectorEnrichmentJobResponse' :: Text
executionRoleArn = Text
pExecutionRoleArn_,
        $sel:inputConfig:StartVectorEnrichmentJobResponse' :: VectorEnrichmentJobInputConfig
inputConfig = VectorEnrichmentJobInputConfig
pInputConfig_,
        $sel:jobConfig:StartVectorEnrichmentJobResponse' :: VectorEnrichmentJobConfig
jobConfig = VectorEnrichmentJobConfig
pJobConfig_,
        $sel:name:StartVectorEnrichmentJobResponse' :: Text
name = Text
pName_,
        $sel:status:StartVectorEnrichmentJobResponse' :: VectorEnrichmentJobStatus
status = VectorEnrichmentJobStatus
pStatus_,
        $sel:type':StartVectorEnrichmentJobResponse' :: VectorEnrichmentJobType
type' = VectorEnrichmentJobType
pType_
      }

-- | The Amazon Key Management Service (KMS) key ID for server-side
-- encryption.
startVectorEnrichmentJobResponse_kmsKeyId :: Lens.Lens' StartVectorEnrichmentJobResponse (Prelude.Maybe Prelude.Text)
startVectorEnrichmentJobResponse_kmsKeyId :: Lens' StartVectorEnrichmentJobResponse (Maybe Text)
startVectorEnrichmentJobResponse_kmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartVectorEnrichmentJobResponse' {Maybe Text
kmsKeyId :: Maybe Text
$sel:kmsKeyId:StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> Maybe Text
kmsKeyId} -> Maybe Text
kmsKeyId) (\s :: StartVectorEnrichmentJobResponse
s@StartVectorEnrichmentJobResponse' {} Maybe Text
a -> StartVectorEnrichmentJobResponse
s {$sel:kmsKeyId:StartVectorEnrichmentJobResponse' :: Maybe Text
kmsKeyId = Maybe Text
a} :: StartVectorEnrichmentJobResponse)

-- | Each tag consists of a key and a value.
startVectorEnrichmentJobResponse_tags :: Lens.Lens' StartVectorEnrichmentJobResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
startVectorEnrichmentJobResponse_tags :: Lens' StartVectorEnrichmentJobResponse (Maybe (HashMap Text Text))
startVectorEnrichmentJobResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartVectorEnrichmentJobResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: StartVectorEnrichmentJobResponse
s@StartVectorEnrichmentJobResponse' {} Maybe (HashMap Text Text)
a -> StartVectorEnrichmentJobResponse
s {$sel:tags:StartVectorEnrichmentJobResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: StartVectorEnrichmentJobResponse) 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.
startVectorEnrichmentJobResponse_httpStatus :: Lens.Lens' StartVectorEnrichmentJobResponse Prelude.Int
startVectorEnrichmentJobResponse_httpStatus :: Lens' StartVectorEnrichmentJobResponse Int
startVectorEnrichmentJobResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartVectorEnrichmentJobResponse' {Int
httpStatus :: Int
$sel:httpStatus:StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: StartVectorEnrichmentJobResponse
s@StartVectorEnrichmentJobResponse' {} Int
a -> StartVectorEnrichmentJobResponse
s {$sel:httpStatus:StartVectorEnrichmentJobResponse' :: Int
httpStatus = Int
a} :: StartVectorEnrichmentJobResponse)

-- | The Amazon Resource Name (ARN) of the Vector Enrichment job.
startVectorEnrichmentJobResponse_arn :: Lens.Lens' StartVectorEnrichmentJobResponse Prelude.Text
startVectorEnrichmentJobResponse_arn :: Lens' StartVectorEnrichmentJobResponse Text
startVectorEnrichmentJobResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartVectorEnrichmentJobResponse' {Text
arn :: Text
$sel:arn:StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> Text
arn} -> Text
arn) (\s :: StartVectorEnrichmentJobResponse
s@StartVectorEnrichmentJobResponse' {} Text
a -> StartVectorEnrichmentJobResponse
s {$sel:arn:StartVectorEnrichmentJobResponse' :: Text
arn = Text
a} :: StartVectorEnrichmentJobResponse)

-- | The creation time.
startVectorEnrichmentJobResponse_creationTime :: Lens.Lens' StartVectorEnrichmentJobResponse Prelude.UTCTime
startVectorEnrichmentJobResponse_creationTime :: Lens' StartVectorEnrichmentJobResponse UTCTime
startVectorEnrichmentJobResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartVectorEnrichmentJobResponse' {POSIX
creationTime :: POSIX
$sel:creationTime:StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> POSIX
creationTime} -> POSIX
creationTime) (\s :: StartVectorEnrichmentJobResponse
s@StartVectorEnrichmentJobResponse' {} POSIX
a -> StartVectorEnrichmentJobResponse
s {$sel:creationTime:StartVectorEnrichmentJobResponse' :: POSIX
creationTime = POSIX
a} :: StartVectorEnrichmentJobResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The duration of the Vector Enrichment job, in seconds.
startVectorEnrichmentJobResponse_durationInSeconds :: Lens.Lens' StartVectorEnrichmentJobResponse Prelude.Int
startVectorEnrichmentJobResponse_durationInSeconds :: Lens' StartVectorEnrichmentJobResponse Int
startVectorEnrichmentJobResponse_durationInSeconds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartVectorEnrichmentJobResponse' {Int
durationInSeconds :: Int
$sel:durationInSeconds:StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> Int
durationInSeconds} -> Int
durationInSeconds) (\s :: StartVectorEnrichmentJobResponse
s@StartVectorEnrichmentJobResponse' {} Int
a -> StartVectorEnrichmentJobResponse
s {$sel:durationInSeconds:StartVectorEnrichmentJobResponse' :: Int
durationInSeconds = Int
a} :: StartVectorEnrichmentJobResponse)

-- | The Amazon Resource Name (ARN) of the IAM role that you specified for
-- the job.
startVectorEnrichmentJobResponse_executionRoleArn :: Lens.Lens' StartVectorEnrichmentJobResponse Prelude.Text
startVectorEnrichmentJobResponse_executionRoleArn :: Lens' StartVectorEnrichmentJobResponse Text
startVectorEnrichmentJobResponse_executionRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartVectorEnrichmentJobResponse' {Text
executionRoleArn :: Text
$sel:executionRoleArn:StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> Text
executionRoleArn} -> Text
executionRoleArn) (\s :: StartVectorEnrichmentJobResponse
s@StartVectorEnrichmentJobResponse' {} Text
a -> StartVectorEnrichmentJobResponse
s {$sel:executionRoleArn:StartVectorEnrichmentJobResponse' :: Text
executionRoleArn = Text
a} :: StartVectorEnrichmentJobResponse)

-- | Input configuration information for starting the Vector Enrichment job.
startVectorEnrichmentJobResponse_inputConfig :: Lens.Lens' StartVectorEnrichmentJobResponse VectorEnrichmentJobInputConfig
startVectorEnrichmentJobResponse_inputConfig :: Lens'
  StartVectorEnrichmentJobResponse VectorEnrichmentJobInputConfig
startVectorEnrichmentJobResponse_inputConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartVectorEnrichmentJobResponse' {VectorEnrichmentJobInputConfig
inputConfig :: VectorEnrichmentJobInputConfig
$sel:inputConfig:StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> VectorEnrichmentJobInputConfig
inputConfig} -> VectorEnrichmentJobInputConfig
inputConfig) (\s :: StartVectorEnrichmentJobResponse
s@StartVectorEnrichmentJobResponse' {} VectorEnrichmentJobInputConfig
a -> StartVectorEnrichmentJobResponse
s {$sel:inputConfig:StartVectorEnrichmentJobResponse' :: VectorEnrichmentJobInputConfig
inputConfig = VectorEnrichmentJobInputConfig
a} :: StartVectorEnrichmentJobResponse)

-- | An object containing information about the job configuration.
startVectorEnrichmentJobResponse_jobConfig :: Lens.Lens' StartVectorEnrichmentJobResponse VectorEnrichmentJobConfig
startVectorEnrichmentJobResponse_jobConfig :: Lens' StartVectorEnrichmentJobResponse VectorEnrichmentJobConfig
startVectorEnrichmentJobResponse_jobConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartVectorEnrichmentJobResponse' {VectorEnrichmentJobConfig
jobConfig :: VectorEnrichmentJobConfig
$sel:jobConfig:StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> VectorEnrichmentJobConfig
jobConfig} -> VectorEnrichmentJobConfig
jobConfig) (\s :: StartVectorEnrichmentJobResponse
s@StartVectorEnrichmentJobResponse' {} VectorEnrichmentJobConfig
a -> StartVectorEnrichmentJobResponse
s {$sel:jobConfig:StartVectorEnrichmentJobResponse' :: VectorEnrichmentJobConfig
jobConfig = VectorEnrichmentJobConfig
a} :: StartVectorEnrichmentJobResponse)

-- | The name of the Vector Enrichment job.
startVectorEnrichmentJobResponse_name :: Lens.Lens' StartVectorEnrichmentJobResponse Prelude.Text
startVectorEnrichmentJobResponse_name :: Lens' StartVectorEnrichmentJobResponse Text
startVectorEnrichmentJobResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartVectorEnrichmentJobResponse' {Text
name :: Text
$sel:name:StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> Text
name} -> Text
name) (\s :: StartVectorEnrichmentJobResponse
s@StartVectorEnrichmentJobResponse' {} Text
a -> StartVectorEnrichmentJobResponse
s {$sel:name:StartVectorEnrichmentJobResponse' :: Text
name = Text
a} :: StartVectorEnrichmentJobResponse)

-- | The status of the Vector Enrichment job being started.
startVectorEnrichmentJobResponse_status :: Lens.Lens' StartVectorEnrichmentJobResponse VectorEnrichmentJobStatus
startVectorEnrichmentJobResponse_status :: Lens' StartVectorEnrichmentJobResponse VectorEnrichmentJobStatus
startVectorEnrichmentJobResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartVectorEnrichmentJobResponse' {VectorEnrichmentJobStatus
status :: VectorEnrichmentJobStatus
$sel:status:StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> VectorEnrichmentJobStatus
status} -> VectorEnrichmentJobStatus
status) (\s :: StartVectorEnrichmentJobResponse
s@StartVectorEnrichmentJobResponse' {} VectorEnrichmentJobStatus
a -> StartVectorEnrichmentJobResponse
s {$sel:status:StartVectorEnrichmentJobResponse' :: VectorEnrichmentJobStatus
status = VectorEnrichmentJobStatus
a} :: StartVectorEnrichmentJobResponse)

-- | The type of the Vector Enrichment job.
startVectorEnrichmentJobResponse_type :: Lens.Lens' StartVectorEnrichmentJobResponse VectorEnrichmentJobType
startVectorEnrichmentJobResponse_type :: Lens' StartVectorEnrichmentJobResponse VectorEnrichmentJobType
startVectorEnrichmentJobResponse_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartVectorEnrichmentJobResponse' {VectorEnrichmentJobType
type' :: VectorEnrichmentJobType
$sel:type':StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> VectorEnrichmentJobType
type'} -> VectorEnrichmentJobType
type') (\s :: StartVectorEnrichmentJobResponse
s@StartVectorEnrichmentJobResponse' {} VectorEnrichmentJobType
a -> StartVectorEnrichmentJobResponse
s {$sel:type':StartVectorEnrichmentJobResponse' :: VectorEnrichmentJobType
type' = VectorEnrichmentJobType
a} :: StartVectorEnrichmentJobResponse)

instance
  Prelude.NFData
    StartVectorEnrichmentJobResponse
  where
  rnf :: StartVectorEnrichmentJobResponse -> ()
rnf StartVectorEnrichmentJobResponse' {Int
Maybe Text
Maybe (HashMap Text Text)
Text
POSIX
VectorEnrichmentJobConfig
VectorEnrichmentJobInputConfig
VectorEnrichmentJobStatus
VectorEnrichmentJobType
type' :: VectorEnrichmentJobType
status :: VectorEnrichmentJobStatus
name :: Text
jobConfig :: VectorEnrichmentJobConfig
inputConfig :: VectorEnrichmentJobInputConfig
executionRoleArn :: Text
durationInSeconds :: Int
creationTime :: POSIX
arn :: Text
httpStatus :: Int
tags :: Maybe (HashMap Text Text)
kmsKeyId :: Maybe Text
$sel:type':StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> VectorEnrichmentJobType
$sel:status:StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> VectorEnrichmentJobStatus
$sel:name:StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> Text
$sel:jobConfig:StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> VectorEnrichmentJobConfig
$sel:inputConfig:StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> VectorEnrichmentJobInputConfig
$sel:executionRoleArn:StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> Text
$sel:durationInSeconds:StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> Int
$sel:creationTime:StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> POSIX
$sel:arn:StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> Text
$sel:httpStatus:StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> Int
$sel:tags:StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> Maybe (HashMap Text Text)
$sel:kmsKeyId:StartVectorEnrichmentJobResponse' :: StartVectorEnrichmentJobResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kmsKeyId
      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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
durationInSeconds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
executionRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf VectorEnrichmentJobInputConfig
inputConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf VectorEnrichmentJobConfig
jobConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf VectorEnrichmentJobStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf VectorEnrichmentJobType
type'