{-# 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.ImageBuilder.CreateImage
-- 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 new image. This request will create a new image along with all
-- of the configured output resources defined in the distribution
-- configuration. You must specify exactly one recipe for your image, using
-- either a ContainerRecipeArn or an ImageRecipeArn.
module Amazonka.ImageBuilder.CreateImage
  ( -- * Creating a Request
    CreateImage (..),
    newCreateImage,

    -- * Request Lenses
    createImage_containerRecipeArn,
    createImage_distributionConfigurationArn,
    createImage_enhancedImageMetadataEnabled,
    createImage_imageRecipeArn,
    createImage_imageTestsConfiguration,
    createImage_tags,
    createImage_infrastructureConfigurationArn,
    createImage_clientToken,

    -- * Destructuring the Response
    CreateImageResponse (..),
    newCreateImageResponse,

    -- * Response Lenses
    createImageResponse_clientToken,
    createImageResponse_imageBuildVersionArn,
    createImageResponse_requestId,
    createImageResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCreateImage' smart constructor.
data CreateImage = CreateImage'
  { -- | The Amazon Resource Name (ARN) of the container recipe that defines how
    -- images are configured and tested.
    CreateImage -> Maybe Text
containerRecipeArn :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the distribution configuration that
    -- defines and configures the outputs of your pipeline.
    CreateImage -> Maybe Text
distributionConfigurationArn :: Prelude.Maybe Prelude.Text,
    -- | Collects additional information about the image being created, including
    -- the operating system (OS) version and package list. This information is
    -- used to enhance the overall experience of using EC2 Image Builder.
    -- Enabled by default.
    CreateImage -> Maybe Bool
enhancedImageMetadataEnabled :: Prelude.Maybe Prelude.Bool,
    -- | The Amazon Resource Name (ARN) of the image recipe that defines how
    -- images are configured, tested, and assessed.
    CreateImage -> Maybe Text
imageRecipeArn :: Prelude.Maybe Prelude.Text,
    -- | The image tests configuration of the image.
    CreateImage -> Maybe ImageTestsConfiguration
imageTestsConfiguration :: Prelude.Maybe ImageTestsConfiguration,
    -- | The tags of the image.
    CreateImage -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The Amazon Resource Name (ARN) of the infrastructure configuration that
    -- defines the environment in which your image will be built and tested.
    CreateImage -> Text
infrastructureConfigurationArn :: Prelude.Text,
    -- | The idempotency token used to make this request idempotent.
    CreateImage -> Text
clientToken :: Prelude.Text
  }
  deriving (CreateImage -> CreateImage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateImage -> CreateImage -> Bool
$c/= :: CreateImage -> CreateImage -> Bool
== :: CreateImage -> CreateImage -> Bool
$c== :: CreateImage -> CreateImage -> Bool
Prelude.Eq, ReadPrec [CreateImage]
ReadPrec CreateImage
Int -> ReadS CreateImage
ReadS [CreateImage]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateImage]
$creadListPrec :: ReadPrec [CreateImage]
readPrec :: ReadPrec CreateImage
$creadPrec :: ReadPrec CreateImage
readList :: ReadS [CreateImage]
$creadList :: ReadS [CreateImage]
readsPrec :: Int -> ReadS CreateImage
$creadsPrec :: Int -> ReadS CreateImage
Prelude.Read, Int -> CreateImage -> ShowS
[CreateImage] -> ShowS
CreateImage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateImage] -> ShowS
$cshowList :: [CreateImage] -> ShowS
show :: CreateImage -> String
$cshow :: CreateImage -> String
showsPrec :: Int -> CreateImage -> ShowS
$cshowsPrec :: Int -> CreateImage -> ShowS
Prelude.Show, forall x. Rep CreateImage x -> CreateImage
forall x. CreateImage -> Rep CreateImage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateImage x -> CreateImage
$cfrom :: forall x. CreateImage -> Rep CreateImage x
Prelude.Generic)

-- |
-- Create a value of 'CreateImage' 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:
--
-- 'containerRecipeArn', 'createImage_containerRecipeArn' - The Amazon Resource Name (ARN) of the container recipe that defines how
-- images are configured and tested.
--
-- 'distributionConfigurationArn', 'createImage_distributionConfigurationArn' - The Amazon Resource Name (ARN) of the distribution configuration that
-- defines and configures the outputs of your pipeline.
--
-- 'enhancedImageMetadataEnabled', 'createImage_enhancedImageMetadataEnabled' - Collects additional information about the image being created, including
-- the operating system (OS) version and package list. This information is
-- used to enhance the overall experience of using EC2 Image Builder.
-- Enabled by default.
--
-- 'imageRecipeArn', 'createImage_imageRecipeArn' - The Amazon Resource Name (ARN) of the image recipe that defines how
-- images are configured, tested, and assessed.
--
-- 'imageTestsConfiguration', 'createImage_imageTestsConfiguration' - The image tests configuration of the image.
--
-- 'tags', 'createImage_tags' - The tags of the image.
--
-- 'infrastructureConfigurationArn', 'createImage_infrastructureConfigurationArn' - The Amazon Resource Name (ARN) of the infrastructure configuration that
-- defines the environment in which your image will be built and tested.
--
-- 'clientToken', 'createImage_clientToken' - The idempotency token used to make this request idempotent.
newCreateImage ::
  -- | 'infrastructureConfigurationArn'
  Prelude.Text ->
  -- | 'clientToken'
  Prelude.Text ->
  CreateImage
newCreateImage :: Text -> Text -> CreateImage
newCreateImage
  Text
pInfrastructureConfigurationArn_
  Text
pClientToken_ =
    CreateImage'
      { $sel:containerRecipeArn:CreateImage' :: Maybe Text
containerRecipeArn = forall a. Maybe a
Prelude.Nothing,
        $sel:distributionConfigurationArn:CreateImage' :: Maybe Text
distributionConfigurationArn = forall a. Maybe a
Prelude.Nothing,
        $sel:enhancedImageMetadataEnabled:CreateImage' :: Maybe Bool
enhancedImageMetadataEnabled = forall a. Maybe a
Prelude.Nothing,
        $sel:imageRecipeArn:CreateImage' :: Maybe Text
imageRecipeArn = forall a. Maybe a
Prelude.Nothing,
        $sel:imageTestsConfiguration:CreateImage' :: Maybe ImageTestsConfiguration
imageTestsConfiguration = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateImage' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:infrastructureConfigurationArn:CreateImage' :: Text
infrastructureConfigurationArn =
          Text
pInfrastructureConfigurationArn_,
        $sel:clientToken:CreateImage' :: Text
clientToken = Text
pClientToken_
      }

-- | The Amazon Resource Name (ARN) of the container recipe that defines how
-- images are configured and tested.
createImage_containerRecipeArn :: Lens.Lens' CreateImage (Prelude.Maybe Prelude.Text)
createImage_containerRecipeArn :: Lens' CreateImage (Maybe Text)
createImage_containerRecipeArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImage' {Maybe Text
containerRecipeArn :: Maybe Text
$sel:containerRecipeArn:CreateImage' :: CreateImage -> Maybe Text
containerRecipeArn} -> Maybe Text
containerRecipeArn) (\s :: CreateImage
s@CreateImage' {} Maybe Text
a -> CreateImage
s {$sel:containerRecipeArn:CreateImage' :: Maybe Text
containerRecipeArn = Maybe Text
a} :: CreateImage)

-- | The Amazon Resource Name (ARN) of the distribution configuration that
-- defines and configures the outputs of your pipeline.
createImage_distributionConfigurationArn :: Lens.Lens' CreateImage (Prelude.Maybe Prelude.Text)
createImage_distributionConfigurationArn :: Lens' CreateImage (Maybe Text)
createImage_distributionConfigurationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImage' {Maybe Text
distributionConfigurationArn :: Maybe Text
$sel:distributionConfigurationArn:CreateImage' :: CreateImage -> Maybe Text
distributionConfigurationArn} -> Maybe Text
distributionConfigurationArn) (\s :: CreateImage
s@CreateImage' {} Maybe Text
a -> CreateImage
s {$sel:distributionConfigurationArn:CreateImage' :: Maybe Text
distributionConfigurationArn = Maybe Text
a} :: CreateImage)

-- | Collects additional information about the image being created, including
-- the operating system (OS) version and package list. This information is
-- used to enhance the overall experience of using EC2 Image Builder.
-- Enabled by default.
createImage_enhancedImageMetadataEnabled :: Lens.Lens' CreateImage (Prelude.Maybe Prelude.Bool)
createImage_enhancedImageMetadataEnabled :: Lens' CreateImage (Maybe Bool)
createImage_enhancedImageMetadataEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImage' {Maybe Bool
enhancedImageMetadataEnabled :: Maybe Bool
$sel:enhancedImageMetadataEnabled:CreateImage' :: CreateImage -> Maybe Bool
enhancedImageMetadataEnabled} -> Maybe Bool
enhancedImageMetadataEnabled) (\s :: CreateImage
s@CreateImage' {} Maybe Bool
a -> CreateImage
s {$sel:enhancedImageMetadataEnabled:CreateImage' :: Maybe Bool
enhancedImageMetadataEnabled = Maybe Bool
a} :: CreateImage)

-- | The Amazon Resource Name (ARN) of the image recipe that defines how
-- images are configured, tested, and assessed.
createImage_imageRecipeArn :: Lens.Lens' CreateImage (Prelude.Maybe Prelude.Text)
createImage_imageRecipeArn :: Lens' CreateImage (Maybe Text)
createImage_imageRecipeArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImage' {Maybe Text
imageRecipeArn :: Maybe Text
$sel:imageRecipeArn:CreateImage' :: CreateImage -> Maybe Text
imageRecipeArn} -> Maybe Text
imageRecipeArn) (\s :: CreateImage
s@CreateImage' {} Maybe Text
a -> CreateImage
s {$sel:imageRecipeArn:CreateImage' :: Maybe Text
imageRecipeArn = Maybe Text
a} :: CreateImage)

-- | The image tests configuration of the image.
createImage_imageTestsConfiguration :: Lens.Lens' CreateImage (Prelude.Maybe ImageTestsConfiguration)
createImage_imageTestsConfiguration :: Lens' CreateImage (Maybe ImageTestsConfiguration)
createImage_imageTestsConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImage' {Maybe ImageTestsConfiguration
imageTestsConfiguration :: Maybe ImageTestsConfiguration
$sel:imageTestsConfiguration:CreateImage' :: CreateImage -> Maybe ImageTestsConfiguration
imageTestsConfiguration} -> Maybe ImageTestsConfiguration
imageTestsConfiguration) (\s :: CreateImage
s@CreateImage' {} Maybe ImageTestsConfiguration
a -> CreateImage
s {$sel:imageTestsConfiguration:CreateImage' :: Maybe ImageTestsConfiguration
imageTestsConfiguration = Maybe ImageTestsConfiguration
a} :: CreateImage)

-- | The tags of the image.
createImage_tags :: Lens.Lens' CreateImage (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createImage_tags :: Lens' CreateImage (Maybe (HashMap Text Text))
createImage_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImage' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateImage' :: CreateImage -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateImage
s@CreateImage' {} Maybe (HashMap Text Text)
a -> CreateImage
s {$sel:tags:CreateImage' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateImage) 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 infrastructure configuration that
-- defines the environment in which your image will be built and tested.
createImage_infrastructureConfigurationArn :: Lens.Lens' CreateImage Prelude.Text
createImage_infrastructureConfigurationArn :: Lens' CreateImage Text
createImage_infrastructureConfigurationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImage' {Text
infrastructureConfigurationArn :: Text
$sel:infrastructureConfigurationArn:CreateImage' :: CreateImage -> Text
infrastructureConfigurationArn} -> Text
infrastructureConfigurationArn) (\s :: CreateImage
s@CreateImage' {} Text
a -> CreateImage
s {$sel:infrastructureConfigurationArn:CreateImage' :: Text
infrastructureConfigurationArn = Text
a} :: CreateImage)

-- | The idempotency token used to make this request idempotent.
createImage_clientToken :: Lens.Lens' CreateImage Prelude.Text
createImage_clientToken :: Lens' CreateImage Text
createImage_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImage' {Text
clientToken :: Text
$sel:clientToken:CreateImage' :: CreateImage -> Text
clientToken} -> Text
clientToken) (\s :: CreateImage
s@CreateImage' {} Text
a -> CreateImage
s {$sel:clientToken:CreateImage' :: Text
clientToken = Text
a} :: CreateImage)

instance Core.AWSRequest CreateImage where
  type AWSResponse CreateImage = CreateImageResponse
  request :: (Service -> Service) -> CreateImage -> Request CreateImage
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateImage
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateImage)))
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 Text -> Int -> CreateImageResponse
CreateImageResponse'
            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
"clientToken")
            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
"imageBuildVersionArn")
            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
"requestId")
            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 CreateImage where
  hashWithSalt :: Int -> CreateImage -> Int
hashWithSalt Int
_salt CreateImage' {Maybe Bool
Maybe Text
Maybe (HashMap Text Text)
Maybe ImageTestsConfiguration
Text
clientToken :: Text
infrastructureConfigurationArn :: Text
tags :: Maybe (HashMap Text Text)
imageTestsConfiguration :: Maybe ImageTestsConfiguration
imageRecipeArn :: Maybe Text
enhancedImageMetadataEnabled :: Maybe Bool
distributionConfigurationArn :: Maybe Text
containerRecipeArn :: Maybe Text
$sel:clientToken:CreateImage' :: CreateImage -> Text
$sel:infrastructureConfigurationArn:CreateImage' :: CreateImage -> Text
$sel:tags:CreateImage' :: CreateImage -> Maybe (HashMap Text Text)
$sel:imageTestsConfiguration:CreateImage' :: CreateImage -> Maybe ImageTestsConfiguration
$sel:imageRecipeArn:CreateImage' :: CreateImage -> Maybe Text
$sel:enhancedImageMetadataEnabled:CreateImage' :: CreateImage -> Maybe Bool
$sel:distributionConfigurationArn:CreateImage' :: CreateImage -> Maybe Text
$sel:containerRecipeArn:CreateImage' :: CreateImage -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
containerRecipeArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
distributionConfigurationArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
enhancedImageMetadataEnabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
imageRecipeArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ImageTestsConfiguration
imageTestsConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
infrastructureConfigurationArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clientToken

instance Prelude.NFData CreateImage where
  rnf :: CreateImage -> ()
rnf CreateImage' {Maybe Bool
Maybe Text
Maybe (HashMap Text Text)
Maybe ImageTestsConfiguration
Text
clientToken :: Text
infrastructureConfigurationArn :: Text
tags :: Maybe (HashMap Text Text)
imageTestsConfiguration :: Maybe ImageTestsConfiguration
imageRecipeArn :: Maybe Text
enhancedImageMetadataEnabled :: Maybe Bool
distributionConfigurationArn :: Maybe Text
containerRecipeArn :: Maybe Text
$sel:clientToken:CreateImage' :: CreateImage -> Text
$sel:infrastructureConfigurationArn:CreateImage' :: CreateImage -> Text
$sel:tags:CreateImage' :: CreateImage -> Maybe (HashMap Text Text)
$sel:imageTestsConfiguration:CreateImage' :: CreateImage -> Maybe ImageTestsConfiguration
$sel:imageRecipeArn:CreateImage' :: CreateImage -> Maybe Text
$sel:enhancedImageMetadataEnabled:CreateImage' :: CreateImage -> Maybe Bool
$sel:distributionConfigurationArn:CreateImage' :: CreateImage -> Maybe Text
$sel:containerRecipeArn:CreateImage' :: CreateImage -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
containerRecipeArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
distributionConfigurationArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
enhancedImageMetadataEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
imageRecipeArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ImageTestsConfiguration
imageTestsConfiguration
      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
infrastructureConfigurationArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
clientToken

instance Data.ToHeaders CreateImage where
  toHeaders :: CreateImage -> 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 CreateImage where
  toJSON :: CreateImage -> Value
toJSON CreateImage' {Maybe Bool
Maybe Text
Maybe (HashMap Text Text)
Maybe ImageTestsConfiguration
Text
clientToken :: Text
infrastructureConfigurationArn :: Text
tags :: Maybe (HashMap Text Text)
imageTestsConfiguration :: Maybe ImageTestsConfiguration
imageRecipeArn :: Maybe Text
enhancedImageMetadataEnabled :: Maybe Bool
distributionConfigurationArn :: Maybe Text
containerRecipeArn :: Maybe Text
$sel:clientToken:CreateImage' :: CreateImage -> Text
$sel:infrastructureConfigurationArn:CreateImage' :: CreateImage -> Text
$sel:tags:CreateImage' :: CreateImage -> Maybe (HashMap Text Text)
$sel:imageTestsConfiguration:CreateImage' :: CreateImage -> Maybe ImageTestsConfiguration
$sel:imageRecipeArn:CreateImage' :: CreateImage -> Maybe Text
$sel:enhancedImageMetadataEnabled:CreateImage' :: CreateImage -> Maybe Bool
$sel:distributionConfigurationArn:CreateImage' :: CreateImage -> Maybe Text
$sel:containerRecipeArn:CreateImage' :: CreateImage -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"containerRecipeArn" 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
containerRecipeArn,
            (Key
"distributionConfigurationArn" 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
distributionConfigurationArn,
            (Key
"enhancedImageMetadataEnabled" 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
enhancedImageMetadataEnabled,
            (Key
"imageRecipeArn" 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
imageRecipeArn,
            (Key
"imageTestsConfiguration" 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 ImageTestsConfiguration
imageTestsConfiguration,
            (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
"infrastructureConfigurationArn"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
infrastructureConfigurationArn
              ),
            forall a. a -> Maybe a
Prelude.Just (Key
"clientToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
clientToken)
          ]
      )

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

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

-- | /See:/ 'newCreateImageResponse' smart constructor.
data CreateImageResponse = CreateImageResponse'
  { -- | The idempotency token used to make this request idempotent.
    CreateImageResponse -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the image that was created by this
    -- request.
    CreateImageResponse -> Maybe Text
imageBuildVersionArn :: Prelude.Maybe Prelude.Text,
    -- | The request ID that uniquely identifies this request.
    CreateImageResponse -> Maybe Text
requestId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateImageResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateImageResponse -> CreateImageResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateImageResponse -> CreateImageResponse -> Bool
$c/= :: CreateImageResponse -> CreateImageResponse -> Bool
== :: CreateImageResponse -> CreateImageResponse -> Bool
$c== :: CreateImageResponse -> CreateImageResponse -> Bool
Prelude.Eq, ReadPrec [CreateImageResponse]
ReadPrec CreateImageResponse
Int -> ReadS CreateImageResponse
ReadS [CreateImageResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateImageResponse]
$creadListPrec :: ReadPrec [CreateImageResponse]
readPrec :: ReadPrec CreateImageResponse
$creadPrec :: ReadPrec CreateImageResponse
readList :: ReadS [CreateImageResponse]
$creadList :: ReadS [CreateImageResponse]
readsPrec :: Int -> ReadS CreateImageResponse
$creadsPrec :: Int -> ReadS CreateImageResponse
Prelude.Read, Int -> CreateImageResponse -> ShowS
[CreateImageResponse] -> ShowS
CreateImageResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateImageResponse] -> ShowS
$cshowList :: [CreateImageResponse] -> ShowS
show :: CreateImageResponse -> String
$cshow :: CreateImageResponse -> String
showsPrec :: Int -> CreateImageResponse -> ShowS
$cshowsPrec :: Int -> CreateImageResponse -> ShowS
Prelude.Show, forall x. Rep CreateImageResponse x -> CreateImageResponse
forall x. CreateImageResponse -> Rep CreateImageResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateImageResponse x -> CreateImageResponse
$cfrom :: forall x. CreateImageResponse -> Rep CreateImageResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateImageResponse' 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', 'createImageResponse_clientToken' - The idempotency token used to make this request idempotent.
--
-- 'imageBuildVersionArn', 'createImageResponse_imageBuildVersionArn' - The Amazon Resource Name (ARN) of the image that was created by this
-- request.
--
-- 'requestId', 'createImageResponse_requestId' - The request ID that uniquely identifies this request.
--
-- 'httpStatus', 'createImageResponse_httpStatus' - The response's http status code.
newCreateImageResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateImageResponse
newCreateImageResponse :: Int -> CreateImageResponse
newCreateImageResponse Int
pHttpStatus_ =
  CreateImageResponse'
    { $sel:clientToken:CreateImageResponse' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
      $sel:imageBuildVersionArn:CreateImageResponse' :: Maybe Text
imageBuildVersionArn = forall a. Maybe a
Prelude.Nothing,
      $sel:requestId:CreateImageResponse' :: Maybe Text
requestId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateImageResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The idempotency token used to make this request idempotent.
createImageResponse_clientToken :: Lens.Lens' CreateImageResponse (Prelude.Maybe Prelude.Text)
createImageResponse_clientToken :: Lens' CreateImageResponse (Maybe Text)
createImageResponse_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImageResponse' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:CreateImageResponse' :: CreateImageResponse -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: CreateImageResponse
s@CreateImageResponse' {} Maybe Text
a -> CreateImageResponse
s {$sel:clientToken:CreateImageResponse' :: Maybe Text
clientToken = Maybe Text
a} :: CreateImageResponse)

-- | The Amazon Resource Name (ARN) of the image that was created by this
-- request.
createImageResponse_imageBuildVersionArn :: Lens.Lens' CreateImageResponse (Prelude.Maybe Prelude.Text)
createImageResponse_imageBuildVersionArn :: Lens' CreateImageResponse (Maybe Text)
createImageResponse_imageBuildVersionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImageResponse' {Maybe Text
imageBuildVersionArn :: Maybe Text
$sel:imageBuildVersionArn:CreateImageResponse' :: CreateImageResponse -> Maybe Text
imageBuildVersionArn} -> Maybe Text
imageBuildVersionArn) (\s :: CreateImageResponse
s@CreateImageResponse' {} Maybe Text
a -> CreateImageResponse
s {$sel:imageBuildVersionArn:CreateImageResponse' :: Maybe Text
imageBuildVersionArn = Maybe Text
a} :: CreateImageResponse)

-- | The request ID that uniquely identifies this request.
createImageResponse_requestId :: Lens.Lens' CreateImageResponse (Prelude.Maybe Prelude.Text)
createImageResponse_requestId :: Lens' CreateImageResponse (Maybe Text)
createImageResponse_requestId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImageResponse' {Maybe Text
requestId :: Maybe Text
$sel:requestId:CreateImageResponse' :: CreateImageResponse -> Maybe Text
requestId} -> Maybe Text
requestId) (\s :: CreateImageResponse
s@CreateImageResponse' {} Maybe Text
a -> CreateImageResponse
s {$sel:requestId:CreateImageResponse' :: Maybe Text
requestId = Maybe Text
a} :: CreateImageResponse)

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

instance Prelude.NFData CreateImageResponse where
  rnf :: CreateImageResponse -> ()
rnf CreateImageResponse' {Int
Maybe Text
httpStatus :: Int
requestId :: Maybe Text
imageBuildVersionArn :: Maybe Text
clientToken :: Maybe Text
$sel:httpStatus:CreateImageResponse' :: CreateImageResponse -> Int
$sel:requestId:CreateImageResponse' :: CreateImageResponse -> Maybe Text
$sel:imageBuildVersionArn:CreateImageResponse' :: CreateImageResponse -> Maybe Text
$sel:clientToken:CreateImageResponse' :: CreateImageResponse -> 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
imageBuildVersionArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
requestId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus