{-# 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.RobOMaker.CreateWorldGenerationJob
-- 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 worlds using the specified template.
module Amazonka.RobOMaker.CreateWorldGenerationJob
  ( -- * Creating a Request
    CreateWorldGenerationJob (..),
    newCreateWorldGenerationJob,

    -- * Request Lenses
    createWorldGenerationJob_clientRequestToken,
    createWorldGenerationJob_tags,
    createWorldGenerationJob_worldTags,
    createWorldGenerationJob_template,
    createWorldGenerationJob_worldCount,

    -- * Destructuring the Response
    CreateWorldGenerationJobResponse (..),
    newCreateWorldGenerationJobResponse,

    -- * Response Lenses
    createWorldGenerationJobResponse_arn,
    createWorldGenerationJobResponse_clientRequestToken,
    createWorldGenerationJobResponse_createdAt,
    createWorldGenerationJobResponse_failureCode,
    createWorldGenerationJobResponse_status,
    createWorldGenerationJobResponse_tags,
    createWorldGenerationJobResponse_template,
    createWorldGenerationJobResponse_worldCount,
    createWorldGenerationJobResponse_worldTags,
    createWorldGenerationJobResponse_httpStatus,
  )
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.RobOMaker.Types

-- | /See:/ 'newCreateWorldGenerationJob' smart constructor.
data CreateWorldGenerationJob = CreateWorldGenerationJob'
  { -- | Unique, case-sensitive identifier that you provide to ensure the
    -- idempotency of the request.
    CreateWorldGenerationJob -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    -- | A map that contains tag keys and tag values that are attached to the
    -- world generator job.
    CreateWorldGenerationJob -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | A map that contains tag keys and tag values that are attached to the
    -- generated worlds.
    CreateWorldGenerationJob -> Maybe (HashMap Text Text)
worldTags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The Amazon Resource Name (arn) of the world template describing the
    -- worlds you want to create.
    CreateWorldGenerationJob -> Text
template :: Prelude.Text,
    -- | Information about the world count.
    CreateWorldGenerationJob -> WorldCount
worldCount :: WorldCount
  }
  deriving (CreateWorldGenerationJob -> CreateWorldGenerationJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateWorldGenerationJob -> CreateWorldGenerationJob -> Bool
$c/= :: CreateWorldGenerationJob -> CreateWorldGenerationJob -> Bool
== :: CreateWorldGenerationJob -> CreateWorldGenerationJob -> Bool
$c== :: CreateWorldGenerationJob -> CreateWorldGenerationJob -> Bool
Prelude.Eq, ReadPrec [CreateWorldGenerationJob]
ReadPrec CreateWorldGenerationJob
Int -> ReadS CreateWorldGenerationJob
ReadS [CreateWorldGenerationJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateWorldGenerationJob]
$creadListPrec :: ReadPrec [CreateWorldGenerationJob]
readPrec :: ReadPrec CreateWorldGenerationJob
$creadPrec :: ReadPrec CreateWorldGenerationJob
readList :: ReadS [CreateWorldGenerationJob]
$creadList :: ReadS [CreateWorldGenerationJob]
readsPrec :: Int -> ReadS CreateWorldGenerationJob
$creadsPrec :: Int -> ReadS CreateWorldGenerationJob
Prelude.Read, Int -> CreateWorldGenerationJob -> ShowS
[CreateWorldGenerationJob] -> ShowS
CreateWorldGenerationJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateWorldGenerationJob] -> ShowS
$cshowList :: [CreateWorldGenerationJob] -> ShowS
show :: CreateWorldGenerationJob -> String
$cshow :: CreateWorldGenerationJob -> String
showsPrec :: Int -> CreateWorldGenerationJob -> ShowS
$cshowsPrec :: Int -> CreateWorldGenerationJob -> ShowS
Prelude.Show, forall x.
Rep CreateWorldGenerationJob x -> CreateWorldGenerationJob
forall x.
CreateWorldGenerationJob -> Rep CreateWorldGenerationJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateWorldGenerationJob x -> CreateWorldGenerationJob
$cfrom :: forall x.
CreateWorldGenerationJob -> Rep CreateWorldGenerationJob x
Prelude.Generic)

-- |
-- Create a value of 'CreateWorldGenerationJob' 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:
--
-- 'clientRequestToken', 'createWorldGenerationJob_clientRequestToken' - Unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request.
--
-- 'tags', 'createWorldGenerationJob_tags' - A map that contains tag keys and tag values that are attached to the
-- world generator job.
--
-- 'worldTags', 'createWorldGenerationJob_worldTags' - A map that contains tag keys and tag values that are attached to the
-- generated worlds.
--
-- 'template', 'createWorldGenerationJob_template' - The Amazon Resource Name (arn) of the world template describing the
-- worlds you want to create.
--
-- 'worldCount', 'createWorldGenerationJob_worldCount' - Information about the world count.
newCreateWorldGenerationJob ::
  -- | 'template'
  Prelude.Text ->
  -- | 'worldCount'
  WorldCount ->
  CreateWorldGenerationJob
newCreateWorldGenerationJob :: Text -> WorldCount -> CreateWorldGenerationJob
newCreateWorldGenerationJob Text
pTemplate_ WorldCount
pWorldCount_ =
  CreateWorldGenerationJob'
    { $sel:clientRequestToken:CreateWorldGenerationJob' :: Maybe Text
clientRequestToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateWorldGenerationJob' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:worldTags:CreateWorldGenerationJob' :: Maybe (HashMap Text Text)
worldTags = forall a. Maybe a
Prelude.Nothing,
      $sel:template:CreateWorldGenerationJob' :: Text
template = Text
pTemplate_,
      $sel:worldCount:CreateWorldGenerationJob' :: WorldCount
worldCount = WorldCount
pWorldCount_
    }

-- | Unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request.
createWorldGenerationJob_clientRequestToken :: Lens.Lens' CreateWorldGenerationJob (Prelude.Maybe Prelude.Text)
createWorldGenerationJob_clientRequestToken :: Lens' CreateWorldGenerationJob (Maybe Text)
createWorldGenerationJob_clientRequestToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorldGenerationJob' {Maybe Text
clientRequestToken :: Maybe Text
$sel:clientRequestToken:CreateWorldGenerationJob' :: CreateWorldGenerationJob -> Maybe Text
clientRequestToken} -> Maybe Text
clientRequestToken) (\s :: CreateWorldGenerationJob
s@CreateWorldGenerationJob' {} Maybe Text
a -> CreateWorldGenerationJob
s {$sel:clientRequestToken:CreateWorldGenerationJob' :: Maybe Text
clientRequestToken = Maybe Text
a} :: CreateWorldGenerationJob)

-- | A map that contains tag keys and tag values that are attached to the
-- world generator job.
createWorldGenerationJob_tags :: Lens.Lens' CreateWorldGenerationJob (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createWorldGenerationJob_tags :: Lens' CreateWorldGenerationJob (Maybe (HashMap Text Text))
createWorldGenerationJob_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorldGenerationJob' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateWorldGenerationJob' :: CreateWorldGenerationJob -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateWorldGenerationJob
s@CreateWorldGenerationJob' {} Maybe (HashMap Text Text)
a -> CreateWorldGenerationJob
s {$sel:tags:CreateWorldGenerationJob' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateWorldGenerationJob) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | A map that contains tag keys and tag values that are attached to the
-- generated worlds.
createWorldGenerationJob_worldTags :: Lens.Lens' CreateWorldGenerationJob (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createWorldGenerationJob_worldTags :: Lens' CreateWorldGenerationJob (Maybe (HashMap Text Text))
createWorldGenerationJob_worldTags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorldGenerationJob' {Maybe (HashMap Text Text)
worldTags :: Maybe (HashMap Text Text)
$sel:worldTags:CreateWorldGenerationJob' :: CreateWorldGenerationJob -> Maybe (HashMap Text Text)
worldTags} -> Maybe (HashMap Text Text)
worldTags) (\s :: CreateWorldGenerationJob
s@CreateWorldGenerationJob' {} Maybe (HashMap Text Text)
a -> CreateWorldGenerationJob
s {$sel:worldTags:CreateWorldGenerationJob' :: Maybe (HashMap Text Text)
worldTags = Maybe (HashMap Text Text)
a} :: CreateWorldGenerationJob) 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 world template describing the
-- worlds you want to create.
createWorldGenerationJob_template :: Lens.Lens' CreateWorldGenerationJob Prelude.Text
createWorldGenerationJob_template :: Lens' CreateWorldGenerationJob Text
createWorldGenerationJob_template = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorldGenerationJob' {Text
template :: Text
$sel:template:CreateWorldGenerationJob' :: CreateWorldGenerationJob -> Text
template} -> Text
template) (\s :: CreateWorldGenerationJob
s@CreateWorldGenerationJob' {} Text
a -> CreateWorldGenerationJob
s {$sel:template:CreateWorldGenerationJob' :: Text
template = Text
a} :: CreateWorldGenerationJob)

-- | Information about the world count.
createWorldGenerationJob_worldCount :: Lens.Lens' CreateWorldGenerationJob WorldCount
createWorldGenerationJob_worldCount :: Lens' CreateWorldGenerationJob WorldCount
createWorldGenerationJob_worldCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorldGenerationJob' {WorldCount
worldCount :: WorldCount
$sel:worldCount:CreateWorldGenerationJob' :: CreateWorldGenerationJob -> WorldCount
worldCount} -> WorldCount
worldCount) (\s :: CreateWorldGenerationJob
s@CreateWorldGenerationJob' {} WorldCount
a -> CreateWorldGenerationJob
s {$sel:worldCount:CreateWorldGenerationJob' :: WorldCount
worldCount = WorldCount
a} :: CreateWorldGenerationJob)

instance Core.AWSRequest CreateWorldGenerationJob where
  type
    AWSResponse CreateWorldGenerationJob =
      CreateWorldGenerationJobResponse
  request :: (Service -> Service)
-> CreateWorldGenerationJob -> Request CreateWorldGenerationJob
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 CreateWorldGenerationJob
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateWorldGenerationJob)))
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
-> Maybe POSIX
-> Maybe WorldGenerationJobErrorCode
-> Maybe WorldGenerationJobStatus
-> Maybe (HashMap Text Text)
-> Maybe Text
-> Maybe WorldCount
-> Maybe (HashMap Text Text)
-> Int
-> CreateWorldGenerationJobResponse
CreateWorldGenerationJobResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"arn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"clientRequestToken")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"createdAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"failureCode")
            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
"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 (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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"template")
            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
"worldCount")
            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
"worldTags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable CreateWorldGenerationJob where
  hashWithSalt :: Int -> CreateWorldGenerationJob -> Int
hashWithSalt Int
_salt CreateWorldGenerationJob' {Maybe Text
Maybe (HashMap Text Text)
Text
WorldCount
worldCount :: WorldCount
template :: Text
worldTags :: Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
clientRequestToken :: Maybe Text
$sel:worldCount:CreateWorldGenerationJob' :: CreateWorldGenerationJob -> WorldCount
$sel:template:CreateWorldGenerationJob' :: CreateWorldGenerationJob -> Text
$sel:worldTags:CreateWorldGenerationJob' :: CreateWorldGenerationJob -> Maybe (HashMap Text Text)
$sel:tags:CreateWorldGenerationJob' :: CreateWorldGenerationJob -> Maybe (HashMap Text Text)
$sel:clientRequestToken:CreateWorldGenerationJob' :: CreateWorldGenerationJob -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientRequestToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
worldTags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
template
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` WorldCount
worldCount

instance Prelude.NFData CreateWorldGenerationJob where
  rnf :: CreateWorldGenerationJob -> ()
rnf CreateWorldGenerationJob' {Maybe Text
Maybe (HashMap Text Text)
Text
WorldCount
worldCount :: WorldCount
template :: Text
worldTags :: Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
clientRequestToken :: Maybe Text
$sel:worldCount:CreateWorldGenerationJob' :: CreateWorldGenerationJob -> WorldCount
$sel:template:CreateWorldGenerationJob' :: CreateWorldGenerationJob -> Text
$sel:worldTags:CreateWorldGenerationJob' :: CreateWorldGenerationJob -> Maybe (HashMap Text Text)
$sel:tags:CreateWorldGenerationJob' :: CreateWorldGenerationJob -> Maybe (HashMap Text Text)
$sel:clientRequestToken:CreateWorldGenerationJob' :: CreateWorldGenerationJob -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientRequestToken
      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 Maybe (HashMap Text Text)
worldTags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
template
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf WorldCount
worldCount

instance Data.ToHeaders CreateWorldGenerationJob where
  toHeaders :: CreateWorldGenerationJob -> 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 CreateWorldGenerationJob where
  toJSON :: CreateWorldGenerationJob -> Value
toJSON CreateWorldGenerationJob' {Maybe Text
Maybe (HashMap Text Text)
Text
WorldCount
worldCount :: WorldCount
template :: Text
worldTags :: Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
clientRequestToken :: Maybe Text
$sel:worldCount:CreateWorldGenerationJob' :: CreateWorldGenerationJob -> WorldCount
$sel:template:CreateWorldGenerationJob' :: CreateWorldGenerationJob -> Text
$sel:worldTags:CreateWorldGenerationJob' :: CreateWorldGenerationJob -> Maybe (HashMap Text Text)
$sel:tags:CreateWorldGenerationJob' :: CreateWorldGenerationJob -> Maybe (HashMap Text Text)
$sel:clientRequestToken:CreateWorldGenerationJob' :: CreateWorldGenerationJob -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"clientRequestToken" 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
clientRequestToken,
            (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,
            (Key
"worldTags" 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)
worldTags,
            forall a. a -> Maybe a
Prelude.Just (Key
"template" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
template),
            forall a. a -> Maybe a
Prelude.Just (Key
"worldCount" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= WorldCount
worldCount)
          ]
      )

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

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

-- | /See:/ 'newCreateWorldGenerationJobResponse' smart constructor.
data CreateWorldGenerationJobResponse = CreateWorldGenerationJobResponse'
  { -- | The Amazon Resource Name (ARN) of the world generator job.
    CreateWorldGenerationJobResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | Unique, case-sensitive identifier that you provide to ensure the
    -- idempotency of the request.
    CreateWorldGenerationJobResponse -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    -- | The time, in milliseconds since the epoch, when the world generator job
    -- was created.
    CreateWorldGenerationJobResponse -> Maybe POSIX
createdAt :: Prelude.Maybe Data.POSIX,
    -- | The failure code of the world generator job if it failed:
    --
    -- [InternalServiceError]
    --     Internal service error.
    --
    -- [LimitExceeded]
    --     The requested resource exceeds the maximum number allowed, or the
    --     number of concurrent stream requests exceeds the maximum number
    --     allowed.
    --
    -- [ResourceNotFound]
    --     The specified resource could not be found.
    --
    -- [RequestThrottled]
    --     The request was throttled.
    --
    -- [InvalidInput]
    --     An input parameter in the request is not valid.
    CreateWorldGenerationJobResponse
-> Maybe WorldGenerationJobErrorCode
failureCode :: Prelude.Maybe WorldGenerationJobErrorCode,
    -- | The status of the world generator job.
    --
    -- [Pending]
    --     The world generator job request is pending.
    --
    -- [Running]
    --     The world generator job is running.
    --
    -- [Completed]
    --     The world generator job completed.
    --
    -- [Failed]
    --     The world generator job failed. See @failureCode@ for more
    --     information.
    --
    -- [PartialFailed]
    --     Some worlds did not generate.
    --
    -- [Canceled]
    --     The world generator job was cancelled.
    --
    -- [Canceling]
    --     The world generator job is being cancelled.
    CreateWorldGenerationJobResponse -> Maybe WorldGenerationJobStatus
status :: Prelude.Maybe WorldGenerationJobStatus,
    -- | A map that contains tag keys and tag values that are attached to the
    -- world generator job.
    CreateWorldGenerationJobResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The Amazon Resource Name (arn) of the world template.
    CreateWorldGenerationJobResponse -> Maybe Text
template :: Prelude.Maybe Prelude.Text,
    -- | Information about the world count.
    CreateWorldGenerationJobResponse -> Maybe WorldCount
worldCount :: Prelude.Maybe WorldCount,
    -- | A map that contains tag keys and tag values that are attached to the
    -- generated worlds.
    CreateWorldGenerationJobResponse -> Maybe (HashMap Text Text)
worldTags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The response's http status code.
    CreateWorldGenerationJobResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateWorldGenerationJobResponse
-> CreateWorldGenerationJobResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateWorldGenerationJobResponse
-> CreateWorldGenerationJobResponse -> Bool
$c/= :: CreateWorldGenerationJobResponse
-> CreateWorldGenerationJobResponse -> Bool
== :: CreateWorldGenerationJobResponse
-> CreateWorldGenerationJobResponse -> Bool
$c== :: CreateWorldGenerationJobResponse
-> CreateWorldGenerationJobResponse -> Bool
Prelude.Eq, ReadPrec [CreateWorldGenerationJobResponse]
ReadPrec CreateWorldGenerationJobResponse
Int -> ReadS CreateWorldGenerationJobResponse
ReadS [CreateWorldGenerationJobResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateWorldGenerationJobResponse]
$creadListPrec :: ReadPrec [CreateWorldGenerationJobResponse]
readPrec :: ReadPrec CreateWorldGenerationJobResponse
$creadPrec :: ReadPrec CreateWorldGenerationJobResponse
readList :: ReadS [CreateWorldGenerationJobResponse]
$creadList :: ReadS [CreateWorldGenerationJobResponse]
readsPrec :: Int -> ReadS CreateWorldGenerationJobResponse
$creadsPrec :: Int -> ReadS CreateWorldGenerationJobResponse
Prelude.Read, Int -> CreateWorldGenerationJobResponse -> ShowS
[CreateWorldGenerationJobResponse] -> ShowS
CreateWorldGenerationJobResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateWorldGenerationJobResponse] -> ShowS
$cshowList :: [CreateWorldGenerationJobResponse] -> ShowS
show :: CreateWorldGenerationJobResponse -> String
$cshow :: CreateWorldGenerationJobResponse -> String
showsPrec :: Int -> CreateWorldGenerationJobResponse -> ShowS
$cshowsPrec :: Int -> CreateWorldGenerationJobResponse -> ShowS
Prelude.Show, forall x.
Rep CreateWorldGenerationJobResponse x
-> CreateWorldGenerationJobResponse
forall x.
CreateWorldGenerationJobResponse
-> Rep CreateWorldGenerationJobResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateWorldGenerationJobResponse x
-> CreateWorldGenerationJobResponse
$cfrom :: forall x.
CreateWorldGenerationJobResponse
-> Rep CreateWorldGenerationJobResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateWorldGenerationJobResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'arn', 'createWorldGenerationJobResponse_arn' - The Amazon Resource Name (ARN) of the world generator job.
--
-- 'clientRequestToken', 'createWorldGenerationJobResponse_clientRequestToken' - Unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request.
--
-- 'createdAt', 'createWorldGenerationJobResponse_createdAt' - The time, in milliseconds since the epoch, when the world generator job
-- was created.
--
-- 'failureCode', 'createWorldGenerationJobResponse_failureCode' - The failure code of the world generator job if it failed:
--
-- [InternalServiceError]
--     Internal service error.
--
-- [LimitExceeded]
--     The requested resource exceeds the maximum number allowed, or the
--     number of concurrent stream requests exceeds the maximum number
--     allowed.
--
-- [ResourceNotFound]
--     The specified resource could not be found.
--
-- [RequestThrottled]
--     The request was throttled.
--
-- [InvalidInput]
--     An input parameter in the request is not valid.
--
-- 'status', 'createWorldGenerationJobResponse_status' - The status of the world generator job.
--
-- [Pending]
--     The world generator job request is pending.
--
-- [Running]
--     The world generator job is running.
--
-- [Completed]
--     The world generator job completed.
--
-- [Failed]
--     The world generator job failed. See @failureCode@ for more
--     information.
--
-- [PartialFailed]
--     Some worlds did not generate.
--
-- [Canceled]
--     The world generator job was cancelled.
--
-- [Canceling]
--     The world generator job is being cancelled.
--
-- 'tags', 'createWorldGenerationJobResponse_tags' - A map that contains tag keys and tag values that are attached to the
-- world generator job.
--
-- 'template', 'createWorldGenerationJobResponse_template' - The Amazon Resource Name (arn) of the world template.
--
-- 'worldCount', 'createWorldGenerationJobResponse_worldCount' - Information about the world count.
--
-- 'worldTags', 'createWorldGenerationJobResponse_worldTags' - A map that contains tag keys and tag values that are attached to the
-- generated worlds.
--
-- 'httpStatus', 'createWorldGenerationJobResponse_httpStatus' - The response's http status code.
newCreateWorldGenerationJobResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateWorldGenerationJobResponse
newCreateWorldGenerationJobResponse :: Int -> CreateWorldGenerationJobResponse
newCreateWorldGenerationJobResponse Int
pHttpStatus_ =
  CreateWorldGenerationJobResponse'
    { $sel:arn:CreateWorldGenerationJobResponse' :: Maybe Text
arn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:clientRequestToken:CreateWorldGenerationJobResponse' :: Maybe Text
clientRequestToken = forall a. Maybe a
Prelude.Nothing,
      $sel:createdAt:CreateWorldGenerationJobResponse' :: Maybe POSIX
createdAt = forall a. Maybe a
Prelude.Nothing,
      $sel:failureCode:CreateWorldGenerationJobResponse' :: Maybe WorldGenerationJobErrorCode
failureCode = forall a. Maybe a
Prelude.Nothing,
      $sel:status:CreateWorldGenerationJobResponse' :: Maybe WorldGenerationJobStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateWorldGenerationJobResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:template:CreateWorldGenerationJobResponse' :: Maybe Text
template = forall a. Maybe a
Prelude.Nothing,
      $sel:worldCount:CreateWorldGenerationJobResponse' :: Maybe WorldCount
worldCount = forall a. Maybe a
Prelude.Nothing,
      $sel:worldTags:CreateWorldGenerationJobResponse' :: Maybe (HashMap Text Text)
worldTags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateWorldGenerationJobResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

-- | Unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request.
createWorldGenerationJobResponse_clientRequestToken :: Lens.Lens' CreateWorldGenerationJobResponse (Prelude.Maybe Prelude.Text)
createWorldGenerationJobResponse_clientRequestToken :: Lens' CreateWorldGenerationJobResponse (Maybe Text)
createWorldGenerationJobResponse_clientRequestToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorldGenerationJobResponse' {Maybe Text
clientRequestToken :: Maybe Text
$sel:clientRequestToken:CreateWorldGenerationJobResponse' :: CreateWorldGenerationJobResponse -> Maybe Text
clientRequestToken} -> Maybe Text
clientRequestToken) (\s :: CreateWorldGenerationJobResponse
s@CreateWorldGenerationJobResponse' {} Maybe Text
a -> CreateWorldGenerationJobResponse
s {$sel:clientRequestToken:CreateWorldGenerationJobResponse' :: Maybe Text
clientRequestToken = Maybe Text
a} :: CreateWorldGenerationJobResponse)

-- | The time, in milliseconds since the epoch, when the world generator job
-- was created.
createWorldGenerationJobResponse_createdAt :: Lens.Lens' CreateWorldGenerationJobResponse (Prelude.Maybe Prelude.UTCTime)
createWorldGenerationJobResponse_createdAt :: Lens' CreateWorldGenerationJobResponse (Maybe UTCTime)
createWorldGenerationJobResponse_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorldGenerationJobResponse' {Maybe POSIX
createdAt :: Maybe POSIX
$sel:createdAt:CreateWorldGenerationJobResponse' :: CreateWorldGenerationJobResponse -> Maybe POSIX
createdAt} -> Maybe POSIX
createdAt) (\s :: CreateWorldGenerationJobResponse
s@CreateWorldGenerationJobResponse' {} Maybe POSIX
a -> CreateWorldGenerationJobResponse
s {$sel:createdAt:CreateWorldGenerationJobResponse' :: Maybe POSIX
createdAt = Maybe POSIX
a} :: CreateWorldGenerationJobResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The failure code of the world generator job if it failed:
--
-- [InternalServiceError]
--     Internal service error.
--
-- [LimitExceeded]
--     The requested resource exceeds the maximum number allowed, or the
--     number of concurrent stream requests exceeds the maximum number
--     allowed.
--
-- [ResourceNotFound]
--     The specified resource could not be found.
--
-- [RequestThrottled]
--     The request was throttled.
--
-- [InvalidInput]
--     An input parameter in the request is not valid.
createWorldGenerationJobResponse_failureCode :: Lens.Lens' CreateWorldGenerationJobResponse (Prelude.Maybe WorldGenerationJobErrorCode)
createWorldGenerationJobResponse_failureCode :: Lens'
  CreateWorldGenerationJobResponse
  (Maybe WorldGenerationJobErrorCode)
createWorldGenerationJobResponse_failureCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorldGenerationJobResponse' {Maybe WorldGenerationJobErrorCode
failureCode :: Maybe WorldGenerationJobErrorCode
$sel:failureCode:CreateWorldGenerationJobResponse' :: CreateWorldGenerationJobResponse
-> Maybe WorldGenerationJobErrorCode
failureCode} -> Maybe WorldGenerationJobErrorCode
failureCode) (\s :: CreateWorldGenerationJobResponse
s@CreateWorldGenerationJobResponse' {} Maybe WorldGenerationJobErrorCode
a -> CreateWorldGenerationJobResponse
s {$sel:failureCode:CreateWorldGenerationJobResponse' :: Maybe WorldGenerationJobErrorCode
failureCode = Maybe WorldGenerationJobErrorCode
a} :: CreateWorldGenerationJobResponse)

-- | The status of the world generator job.
--
-- [Pending]
--     The world generator job request is pending.
--
-- [Running]
--     The world generator job is running.
--
-- [Completed]
--     The world generator job completed.
--
-- [Failed]
--     The world generator job failed. See @failureCode@ for more
--     information.
--
-- [PartialFailed]
--     Some worlds did not generate.
--
-- [Canceled]
--     The world generator job was cancelled.
--
-- [Canceling]
--     The world generator job is being cancelled.
createWorldGenerationJobResponse_status :: Lens.Lens' CreateWorldGenerationJobResponse (Prelude.Maybe WorldGenerationJobStatus)
createWorldGenerationJobResponse_status :: Lens'
  CreateWorldGenerationJobResponse (Maybe WorldGenerationJobStatus)
createWorldGenerationJobResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorldGenerationJobResponse' {Maybe WorldGenerationJobStatus
status :: Maybe WorldGenerationJobStatus
$sel:status:CreateWorldGenerationJobResponse' :: CreateWorldGenerationJobResponse -> Maybe WorldGenerationJobStatus
status} -> Maybe WorldGenerationJobStatus
status) (\s :: CreateWorldGenerationJobResponse
s@CreateWorldGenerationJobResponse' {} Maybe WorldGenerationJobStatus
a -> CreateWorldGenerationJobResponse
s {$sel:status:CreateWorldGenerationJobResponse' :: Maybe WorldGenerationJobStatus
status = Maybe WorldGenerationJobStatus
a} :: CreateWorldGenerationJobResponse)

-- | A map that contains tag keys and tag values that are attached to the
-- world generator job.
createWorldGenerationJobResponse_tags :: Lens.Lens' CreateWorldGenerationJobResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createWorldGenerationJobResponse_tags :: Lens' CreateWorldGenerationJobResponse (Maybe (HashMap Text Text))
createWorldGenerationJobResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorldGenerationJobResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateWorldGenerationJobResponse' :: CreateWorldGenerationJobResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateWorldGenerationJobResponse
s@CreateWorldGenerationJobResponse' {} Maybe (HashMap Text Text)
a -> CreateWorldGenerationJobResponse
s {$sel:tags:CreateWorldGenerationJobResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateWorldGenerationJobResponse) 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 world template.
createWorldGenerationJobResponse_template :: Lens.Lens' CreateWorldGenerationJobResponse (Prelude.Maybe Prelude.Text)
createWorldGenerationJobResponse_template :: Lens' CreateWorldGenerationJobResponse (Maybe Text)
createWorldGenerationJobResponse_template = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorldGenerationJobResponse' {Maybe Text
template :: Maybe Text
$sel:template:CreateWorldGenerationJobResponse' :: CreateWorldGenerationJobResponse -> Maybe Text
template} -> Maybe Text
template) (\s :: CreateWorldGenerationJobResponse
s@CreateWorldGenerationJobResponse' {} Maybe Text
a -> CreateWorldGenerationJobResponse
s {$sel:template:CreateWorldGenerationJobResponse' :: Maybe Text
template = Maybe Text
a} :: CreateWorldGenerationJobResponse)

-- | Information about the world count.
createWorldGenerationJobResponse_worldCount :: Lens.Lens' CreateWorldGenerationJobResponse (Prelude.Maybe WorldCount)
createWorldGenerationJobResponse_worldCount :: Lens' CreateWorldGenerationJobResponse (Maybe WorldCount)
createWorldGenerationJobResponse_worldCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorldGenerationJobResponse' {Maybe WorldCount
worldCount :: Maybe WorldCount
$sel:worldCount:CreateWorldGenerationJobResponse' :: CreateWorldGenerationJobResponse -> Maybe WorldCount
worldCount} -> Maybe WorldCount
worldCount) (\s :: CreateWorldGenerationJobResponse
s@CreateWorldGenerationJobResponse' {} Maybe WorldCount
a -> CreateWorldGenerationJobResponse
s {$sel:worldCount:CreateWorldGenerationJobResponse' :: Maybe WorldCount
worldCount = Maybe WorldCount
a} :: CreateWorldGenerationJobResponse)

-- | A map that contains tag keys and tag values that are attached to the
-- generated worlds.
createWorldGenerationJobResponse_worldTags :: Lens.Lens' CreateWorldGenerationJobResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createWorldGenerationJobResponse_worldTags :: Lens' CreateWorldGenerationJobResponse (Maybe (HashMap Text Text))
createWorldGenerationJobResponse_worldTags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorldGenerationJobResponse' {Maybe (HashMap Text Text)
worldTags :: Maybe (HashMap Text Text)
$sel:worldTags:CreateWorldGenerationJobResponse' :: CreateWorldGenerationJobResponse -> Maybe (HashMap Text Text)
worldTags} -> Maybe (HashMap Text Text)
worldTags) (\s :: CreateWorldGenerationJobResponse
s@CreateWorldGenerationJobResponse' {} Maybe (HashMap Text Text)
a -> CreateWorldGenerationJobResponse
s {$sel:worldTags:CreateWorldGenerationJobResponse' :: Maybe (HashMap Text Text)
worldTags = Maybe (HashMap Text Text)
a} :: CreateWorldGenerationJobResponse) 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.
createWorldGenerationJobResponse_httpStatus :: Lens.Lens' CreateWorldGenerationJobResponse Prelude.Int
createWorldGenerationJobResponse_httpStatus :: Lens' CreateWorldGenerationJobResponse Int
createWorldGenerationJobResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorldGenerationJobResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateWorldGenerationJobResponse' :: CreateWorldGenerationJobResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CreateWorldGenerationJobResponse
s@CreateWorldGenerationJobResponse' {} Int
a -> CreateWorldGenerationJobResponse
s {$sel:httpStatus:CreateWorldGenerationJobResponse' :: Int
httpStatus = Int
a} :: CreateWorldGenerationJobResponse)

instance
  Prelude.NFData
    CreateWorldGenerationJobResponse
  where
  rnf :: CreateWorldGenerationJobResponse -> ()
rnf CreateWorldGenerationJobResponse' {Int
Maybe Text
Maybe (HashMap Text Text)
Maybe POSIX
Maybe WorldCount
Maybe WorldGenerationJobErrorCode
Maybe WorldGenerationJobStatus
httpStatus :: Int
worldTags :: Maybe (HashMap Text Text)
worldCount :: Maybe WorldCount
template :: Maybe Text
tags :: Maybe (HashMap Text Text)
status :: Maybe WorldGenerationJobStatus
failureCode :: Maybe WorldGenerationJobErrorCode
createdAt :: Maybe POSIX
clientRequestToken :: Maybe Text
arn :: Maybe Text
$sel:httpStatus:CreateWorldGenerationJobResponse' :: CreateWorldGenerationJobResponse -> Int
$sel:worldTags:CreateWorldGenerationJobResponse' :: CreateWorldGenerationJobResponse -> Maybe (HashMap Text Text)
$sel:worldCount:CreateWorldGenerationJobResponse' :: CreateWorldGenerationJobResponse -> Maybe WorldCount
$sel:template:CreateWorldGenerationJobResponse' :: CreateWorldGenerationJobResponse -> Maybe Text
$sel:tags:CreateWorldGenerationJobResponse' :: CreateWorldGenerationJobResponse -> Maybe (HashMap Text Text)
$sel:status:CreateWorldGenerationJobResponse' :: CreateWorldGenerationJobResponse -> Maybe WorldGenerationJobStatus
$sel:failureCode:CreateWorldGenerationJobResponse' :: CreateWorldGenerationJobResponse
-> Maybe WorldGenerationJobErrorCode
$sel:createdAt:CreateWorldGenerationJobResponse' :: CreateWorldGenerationJobResponse -> Maybe POSIX
$sel:clientRequestToken:CreateWorldGenerationJobResponse' :: CreateWorldGenerationJobResponse -> Maybe Text
$sel:arn:CreateWorldGenerationJobResponse' :: CreateWorldGenerationJobResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientRequestToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe WorldGenerationJobErrorCode
failureCode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe WorldGenerationJobStatus
status
      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 Maybe Text
template
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe WorldCount
worldCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
worldTags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus