{-# 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.CreateImagePipeline
-- 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 pipeline. Image pipelines enable you to automate the
-- creation and distribution of images.
module Amazonka.ImageBuilder.CreateImagePipeline
  ( -- * Creating a Request
    CreateImagePipeline (..),
    newCreateImagePipeline,

    -- * Request Lenses
    createImagePipeline_containerRecipeArn,
    createImagePipeline_description,
    createImagePipeline_distributionConfigurationArn,
    createImagePipeline_enhancedImageMetadataEnabled,
    createImagePipeline_imageRecipeArn,
    createImagePipeline_imageTestsConfiguration,
    createImagePipeline_schedule,
    createImagePipeline_status,
    createImagePipeline_tags,
    createImagePipeline_name,
    createImagePipeline_infrastructureConfigurationArn,
    createImagePipeline_clientToken,

    -- * Destructuring the Response
    CreateImagePipelineResponse (..),
    newCreateImagePipelineResponse,

    -- * Response Lenses
    createImagePipelineResponse_clientToken,
    createImagePipelineResponse_imagePipelineArn,
    createImagePipelineResponse_requestId,
    createImagePipelineResponse_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:/ 'newCreateImagePipeline' smart constructor.
data CreateImagePipeline = CreateImagePipeline'
  { -- | The Amazon Resource Name (ARN) of the container recipe that is used to
    -- configure images created by this container pipeline.
    CreateImagePipeline -> Maybe Text
containerRecipeArn :: Prelude.Maybe Prelude.Text,
    -- | The description of the image pipeline.
    CreateImagePipeline -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the distribution configuration that
    -- will be used to configure and distribute images created by this image
    -- pipeline.
    CreateImagePipeline -> 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.
    CreateImagePipeline -> Maybe Bool
enhancedImageMetadataEnabled :: Prelude.Maybe Prelude.Bool,
    -- | The Amazon Resource Name (ARN) of the image recipe that will be used to
    -- configure images created by this image pipeline.
    CreateImagePipeline -> Maybe Text
imageRecipeArn :: Prelude.Maybe Prelude.Text,
    -- | The image test configuration of the image pipeline.
    CreateImagePipeline -> Maybe ImageTestsConfiguration
imageTestsConfiguration :: Prelude.Maybe ImageTestsConfiguration,
    -- | The schedule of the image pipeline.
    CreateImagePipeline -> Maybe Schedule
schedule :: Prelude.Maybe Schedule,
    -- | The status of the image pipeline.
    CreateImagePipeline -> Maybe PipelineStatus
status :: Prelude.Maybe PipelineStatus,
    -- | The tags of the image pipeline.
    CreateImagePipeline -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The name of the image pipeline.
    CreateImagePipeline -> Text
name :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the infrastructure configuration that
    -- will be used to build images created by this image pipeline.
    CreateImagePipeline -> Text
infrastructureConfigurationArn :: Prelude.Text,
    -- | The idempotency token used to make this request idempotent.
    CreateImagePipeline -> Text
clientToken :: Prelude.Text
  }
  deriving (CreateImagePipeline -> CreateImagePipeline -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateImagePipeline -> CreateImagePipeline -> Bool
$c/= :: CreateImagePipeline -> CreateImagePipeline -> Bool
== :: CreateImagePipeline -> CreateImagePipeline -> Bool
$c== :: CreateImagePipeline -> CreateImagePipeline -> Bool
Prelude.Eq, ReadPrec [CreateImagePipeline]
ReadPrec CreateImagePipeline
Int -> ReadS CreateImagePipeline
ReadS [CreateImagePipeline]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateImagePipeline]
$creadListPrec :: ReadPrec [CreateImagePipeline]
readPrec :: ReadPrec CreateImagePipeline
$creadPrec :: ReadPrec CreateImagePipeline
readList :: ReadS [CreateImagePipeline]
$creadList :: ReadS [CreateImagePipeline]
readsPrec :: Int -> ReadS CreateImagePipeline
$creadsPrec :: Int -> ReadS CreateImagePipeline
Prelude.Read, Int -> CreateImagePipeline -> ShowS
[CreateImagePipeline] -> ShowS
CreateImagePipeline -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateImagePipeline] -> ShowS
$cshowList :: [CreateImagePipeline] -> ShowS
show :: CreateImagePipeline -> String
$cshow :: CreateImagePipeline -> String
showsPrec :: Int -> CreateImagePipeline -> ShowS
$cshowsPrec :: Int -> CreateImagePipeline -> ShowS
Prelude.Show, forall x. Rep CreateImagePipeline x -> CreateImagePipeline
forall x. CreateImagePipeline -> Rep CreateImagePipeline x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateImagePipeline x -> CreateImagePipeline
$cfrom :: forall x. CreateImagePipeline -> Rep CreateImagePipeline x
Prelude.Generic)

-- |
-- Create a value of 'CreateImagePipeline' 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', 'createImagePipeline_containerRecipeArn' - The Amazon Resource Name (ARN) of the container recipe that is used to
-- configure images created by this container pipeline.
--
-- 'description', 'createImagePipeline_description' - The description of the image pipeline.
--
-- 'distributionConfigurationArn', 'createImagePipeline_distributionConfigurationArn' - The Amazon Resource Name (ARN) of the distribution configuration that
-- will be used to configure and distribute images created by this image
-- pipeline.
--
-- 'enhancedImageMetadataEnabled', 'createImagePipeline_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', 'createImagePipeline_imageRecipeArn' - The Amazon Resource Name (ARN) of the image recipe that will be used to
-- configure images created by this image pipeline.
--
-- 'imageTestsConfiguration', 'createImagePipeline_imageTestsConfiguration' - The image test configuration of the image pipeline.
--
-- 'schedule', 'createImagePipeline_schedule' - The schedule of the image pipeline.
--
-- 'status', 'createImagePipeline_status' - The status of the image pipeline.
--
-- 'tags', 'createImagePipeline_tags' - The tags of the image pipeline.
--
-- 'name', 'createImagePipeline_name' - The name of the image pipeline.
--
-- 'infrastructureConfigurationArn', 'createImagePipeline_infrastructureConfigurationArn' - The Amazon Resource Name (ARN) of the infrastructure configuration that
-- will be used to build images created by this image pipeline.
--
-- 'clientToken', 'createImagePipeline_clientToken' - The idempotency token used to make this request idempotent.
newCreateImagePipeline ::
  -- | 'name'
  Prelude.Text ->
  -- | 'infrastructureConfigurationArn'
  Prelude.Text ->
  -- | 'clientToken'
  Prelude.Text ->
  CreateImagePipeline
newCreateImagePipeline :: Text -> Text -> Text -> CreateImagePipeline
newCreateImagePipeline
  Text
pName_
  Text
pInfrastructureConfigurationArn_
  Text
pClientToken_ =
    CreateImagePipeline'
      { $sel:containerRecipeArn:CreateImagePipeline' :: Maybe Text
containerRecipeArn =
          forall a. Maybe a
Prelude.Nothing,
        $sel:description:CreateImagePipeline' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
        $sel:distributionConfigurationArn:CreateImagePipeline' :: Maybe Text
distributionConfigurationArn = forall a. Maybe a
Prelude.Nothing,
        $sel:enhancedImageMetadataEnabled:CreateImagePipeline' :: Maybe Bool
enhancedImageMetadataEnabled = forall a. Maybe a
Prelude.Nothing,
        $sel:imageRecipeArn:CreateImagePipeline' :: Maybe Text
imageRecipeArn = forall a. Maybe a
Prelude.Nothing,
        $sel:imageTestsConfiguration:CreateImagePipeline' :: Maybe ImageTestsConfiguration
imageTestsConfiguration = forall a. Maybe a
Prelude.Nothing,
        $sel:schedule:CreateImagePipeline' :: Maybe Schedule
schedule = forall a. Maybe a
Prelude.Nothing,
        $sel:status:CreateImagePipeline' :: Maybe PipelineStatus
status = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateImagePipeline' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:name:CreateImagePipeline' :: Text
name = Text
pName_,
        $sel:infrastructureConfigurationArn:CreateImagePipeline' :: Text
infrastructureConfigurationArn =
          Text
pInfrastructureConfigurationArn_,
        $sel:clientToken:CreateImagePipeline' :: Text
clientToken = Text
pClientToken_
      }

-- | The Amazon Resource Name (ARN) of the container recipe that is used to
-- configure images created by this container pipeline.
createImagePipeline_containerRecipeArn :: Lens.Lens' CreateImagePipeline (Prelude.Maybe Prelude.Text)
createImagePipeline_containerRecipeArn :: Lens' CreateImagePipeline (Maybe Text)
createImagePipeline_containerRecipeArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImagePipeline' {Maybe Text
containerRecipeArn :: Maybe Text
$sel:containerRecipeArn:CreateImagePipeline' :: CreateImagePipeline -> Maybe Text
containerRecipeArn} -> Maybe Text
containerRecipeArn) (\s :: CreateImagePipeline
s@CreateImagePipeline' {} Maybe Text
a -> CreateImagePipeline
s {$sel:containerRecipeArn:CreateImagePipeline' :: Maybe Text
containerRecipeArn = Maybe Text
a} :: CreateImagePipeline)

-- | The description of the image pipeline.
createImagePipeline_description :: Lens.Lens' CreateImagePipeline (Prelude.Maybe Prelude.Text)
createImagePipeline_description :: Lens' CreateImagePipeline (Maybe Text)
createImagePipeline_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImagePipeline' {Maybe Text
description :: Maybe Text
$sel:description:CreateImagePipeline' :: CreateImagePipeline -> Maybe Text
description} -> Maybe Text
description) (\s :: CreateImagePipeline
s@CreateImagePipeline' {} Maybe Text
a -> CreateImagePipeline
s {$sel:description:CreateImagePipeline' :: Maybe Text
description = Maybe Text
a} :: CreateImagePipeline)

-- | The Amazon Resource Name (ARN) of the distribution configuration that
-- will be used to configure and distribute images created by this image
-- pipeline.
createImagePipeline_distributionConfigurationArn :: Lens.Lens' CreateImagePipeline (Prelude.Maybe Prelude.Text)
createImagePipeline_distributionConfigurationArn :: Lens' CreateImagePipeline (Maybe Text)
createImagePipeline_distributionConfigurationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImagePipeline' {Maybe Text
distributionConfigurationArn :: Maybe Text
$sel:distributionConfigurationArn:CreateImagePipeline' :: CreateImagePipeline -> Maybe Text
distributionConfigurationArn} -> Maybe Text
distributionConfigurationArn) (\s :: CreateImagePipeline
s@CreateImagePipeline' {} Maybe Text
a -> CreateImagePipeline
s {$sel:distributionConfigurationArn:CreateImagePipeline' :: Maybe Text
distributionConfigurationArn = Maybe Text
a} :: CreateImagePipeline)

-- | 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.
createImagePipeline_enhancedImageMetadataEnabled :: Lens.Lens' CreateImagePipeline (Prelude.Maybe Prelude.Bool)
createImagePipeline_enhancedImageMetadataEnabled :: Lens' CreateImagePipeline (Maybe Bool)
createImagePipeline_enhancedImageMetadataEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImagePipeline' {Maybe Bool
enhancedImageMetadataEnabled :: Maybe Bool
$sel:enhancedImageMetadataEnabled:CreateImagePipeline' :: CreateImagePipeline -> Maybe Bool
enhancedImageMetadataEnabled} -> Maybe Bool
enhancedImageMetadataEnabled) (\s :: CreateImagePipeline
s@CreateImagePipeline' {} Maybe Bool
a -> CreateImagePipeline
s {$sel:enhancedImageMetadataEnabled:CreateImagePipeline' :: Maybe Bool
enhancedImageMetadataEnabled = Maybe Bool
a} :: CreateImagePipeline)

-- | The Amazon Resource Name (ARN) of the image recipe that will be used to
-- configure images created by this image pipeline.
createImagePipeline_imageRecipeArn :: Lens.Lens' CreateImagePipeline (Prelude.Maybe Prelude.Text)
createImagePipeline_imageRecipeArn :: Lens' CreateImagePipeline (Maybe Text)
createImagePipeline_imageRecipeArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImagePipeline' {Maybe Text
imageRecipeArn :: Maybe Text
$sel:imageRecipeArn:CreateImagePipeline' :: CreateImagePipeline -> Maybe Text
imageRecipeArn} -> Maybe Text
imageRecipeArn) (\s :: CreateImagePipeline
s@CreateImagePipeline' {} Maybe Text
a -> CreateImagePipeline
s {$sel:imageRecipeArn:CreateImagePipeline' :: Maybe Text
imageRecipeArn = Maybe Text
a} :: CreateImagePipeline)

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

-- | The schedule of the image pipeline.
createImagePipeline_schedule :: Lens.Lens' CreateImagePipeline (Prelude.Maybe Schedule)
createImagePipeline_schedule :: Lens' CreateImagePipeline (Maybe Schedule)
createImagePipeline_schedule = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImagePipeline' {Maybe Schedule
schedule :: Maybe Schedule
$sel:schedule:CreateImagePipeline' :: CreateImagePipeline -> Maybe Schedule
schedule} -> Maybe Schedule
schedule) (\s :: CreateImagePipeline
s@CreateImagePipeline' {} Maybe Schedule
a -> CreateImagePipeline
s {$sel:schedule:CreateImagePipeline' :: Maybe Schedule
schedule = Maybe Schedule
a} :: CreateImagePipeline)

-- | The status of the image pipeline.
createImagePipeline_status :: Lens.Lens' CreateImagePipeline (Prelude.Maybe PipelineStatus)
createImagePipeline_status :: Lens' CreateImagePipeline (Maybe PipelineStatus)
createImagePipeline_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImagePipeline' {Maybe PipelineStatus
status :: Maybe PipelineStatus
$sel:status:CreateImagePipeline' :: CreateImagePipeline -> Maybe PipelineStatus
status} -> Maybe PipelineStatus
status) (\s :: CreateImagePipeline
s@CreateImagePipeline' {} Maybe PipelineStatus
a -> CreateImagePipeline
s {$sel:status:CreateImagePipeline' :: Maybe PipelineStatus
status = Maybe PipelineStatus
a} :: CreateImagePipeline)

-- | The tags of the image pipeline.
createImagePipeline_tags :: Lens.Lens' CreateImagePipeline (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createImagePipeline_tags :: Lens' CreateImagePipeline (Maybe (HashMap Text Text))
createImagePipeline_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImagePipeline' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateImagePipeline' :: CreateImagePipeline -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateImagePipeline
s@CreateImagePipeline' {} Maybe (HashMap Text Text)
a -> CreateImagePipeline
s {$sel:tags:CreateImagePipeline' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateImagePipeline) 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 name of the image pipeline.
createImagePipeline_name :: Lens.Lens' CreateImagePipeline Prelude.Text
createImagePipeline_name :: Lens' CreateImagePipeline Text
createImagePipeline_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImagePipeline' {Text
name :: Text
$sel:name:CreateImagePipeline' :: CreateImagePipeline -> Text
name} -> Text
name) (\s :: CreateImagePipeline
s@CreateImagePipeline' {} Text
a -> CreateImagePipeline
s {$sel:name:CreateImagePipeline' :: Text
name = Text
a} :: CreateImagePipeline)

-- | The Amazon Resource Name (ARN) of the infrastructure configuration that
-- will be used to build images created by this image pipeline.
createImagePipeline_infrastructureConfigurationArn :: Lens.Lens' CreateImagePipeline Prelude.Text
createImagePipeline_infrastructureConfigurationArn :: Lens' CreateImagePipeline Text
createImagePipeline_infrastructureConfigurationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImagePipeline' {Text
infrastructureConfigurationArn :: Text
$sel:infrastructureConfigurationArn:CreateImagePipeline' :: CreateImagePipeline -> Text
infrastructureConfigurationArn} -> Text
infrastructureConfigurationArn) (\s :: CreateImagePipeline
s@CreateImagePipeline' {} Text
a -> CreateImagePipeline
s {$sel:infrastructureConfigurationArn:CreateImagePipeline' :: Text
infrastructureConfigurationArn = Text
a} :: CreateImagePipeline)

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

instance Core.AWSRequest CreateImagePipeline where
  type
    AWSResponse CreateImagePipeline =
      CreateImagePipelineResponse
  request :: (Service -> Service)
-> CreateImagePipeline -> Request CreateImagePipeline
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 CreateImagePipeline
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateImagePipeline)))
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 -> CreateImagePipelineResponse
CreateImagePipelineResponse'
            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
"imagePipelineArn")
            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 CreateImagePipeline where
  hashWithSalt :: Int -> CreateImagePipeline -> Int
hashWithSalt Int
_salt CreateImagePipeline' {Maybe Bool
Maybe Text
Maybe (HashMap Text Text)
Maybe ImageTestsConfiguration
Maybe PipelineStatus
Maybe Schedule
Text
clientToken :: Text
infrastructureConfigurationArn :: Text
name :: Text
tags :: Maybe (HashMap Text Text)
status :: Maybe PipelineStatus
schedule :: Maybe Schedule
imageTestsConfiguration :: Maybe ImageTestsConfiguration
imageRecipeArn :: Maybe Text
enhancedImageMetadataEnabled :: Maybe Bool
distributionConfigurationArn :: Maybe Text
description :: Maybe Text
containerRecipeArn :: Maybe Text
$sel:clientToken:CreateImagePipeline' :: CreateImagePipeline -> Text
$sel:infrastructureConfigurationArn:CreateImagePipeline' :: CreateImagePipeline -> Text
$sel:name:CreateImagePipeline' :: CreateImagePipeline -> Text
$sel:tags:CreateImagePipeline' :: CreateImagePipeline -> Maybe (HashMap Text Text)
$sel:status:CreateImagePipeline' :: CreateImagePipeline -> Maybe PipelineStatus
$sel:schedule:CreateImagePipeline' :: CreateImagePipeline -> Maybe Schedule
$sel:imageTestsConfiguration:CreateImagePipeline' :: CreateImagePipeline -> Maybe ImageTestsConfiguration
$sel:imageRecipeArn:CreateImagePipeline' :: CreateImagePipeline -> Maybe Text
$sel:enhancedImageMetadataEnabled:CreateImagePipeline' :: CreateImagePipeline -> Maybe Bool
$sel:distributionConfigurationArn:CreateImagePipeline' :: CreateImagePipeline -> Maybe Text
$sel:description:CreateImagePipeline' :: CreateImagePipeline -> Maybe Text
$sel:containerRecipeArn:CreateImagePipeline' :: CreateImagePipeline -> 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
description
      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 Schedule
schedule
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PipelineStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      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 CreateImagePipeline where
  rnf :: CreateImagePipeline -> ()
rnf CreateImagePipeline' {Maybe Bool
Maybe Text
Maybe (HashMap Text Text)
Maybe ImageTestsConfiguration
Maybe PipelineStatus
Maybe Schedule
Text
clientToken :: Text
infrastructureConfigurationArn :: Text
name :: Text
tags :: Maybe (HashMap Text Text)
status :: Maybe PipelineStatus
schedule :: Maybe Schedule
imageTestsConfiguration :: Maybe ImageTestsConfiguration
imageRecipeArn :: Maybe Text
enhancedImageMetadataEnabled :: Maybe Bool
distributionConfigurationArn :: Maybe Text
description :: Maybe Text
containerRecipeArn :: Maybe Text
$sel:clientToken:CreateImagePipeline' :: CreateImagePipeline -> Text
$sel:infrastructureConfigurationArn:CreateImagePipeline' :: CreateImagePipeline -> Text
$sel:name:CreateImagePipeline' :: CreateImagePipeline -> Text
$sel:tags:CreateImagePipeline' :: CreateImagePipeline -> Maybe (HashMap Text Text)
$sel:status:CreateImagePipeline' :: CreateImagePipeline -> Maybe PipelineStatus
$sel:schedule:CreateImagePipeline' :: CreateImagePipeline -> Maybe Schedule
$sel:imageTestsConfiguration:CreateImagePipeline' :: CreateImagePipeline -> Maybe ImageTestsConfiguration
$sel:imageRecipeArn:CreateImagePipeline' :: CreateImagePipeline -> Maybe Text
$sel:enhancedImageMetadataEnabled:CreateImagePipeline' :: CreateImagePipeline -> Maybe Bool
$sel:distributionConfigurationArn:CreateImagePipeline' :: CreateImagePipeline -> Maybe Text
$sel:description:CreateImagePipeline' :: CreateImagePipeline -> Maybe Text
$sel:containerRecipeArn:CreateImagePipeline' :: CreateImagePipeline -> 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
description
      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 Schedule
schedule
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PipelineStatus
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 Text
name
      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 CreateImagePipeline where
  toHeaders :: CreateImagePipeline -> 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 CreateImagePipeline where
  toJSON :: CreateImagePipeline -> Value
toJSON CreateImagePipeline' {Maybe Bool
Maybe Text
Maybe (HashMap Text Text)
Maybe ImageTestsConfiguration
Maybe PipelineStatus
Maybe Schedule
Text
clientToken :: Text
infrastructureConfigurationArn :: Text
name :: Text
tags :: Maybe (HashMap Text Text)
status :: Maybe PipelineStatus
schedule :: Maybe Schedule
imageTestsConfiguration :: Maybe ImageTestsConfiguration
imageRecipeArn :: Maybe Text
enhancedImageMetadataEnabled :: Maybe Bool
distributionConfigurationArn :: Maybe Text
description :: Maybe Text
containerRecipeArn :: Maybe Text
$sel:clientToken:CreateImagePipeline' :: CreateImagePipeline -> Text
$sel:infrastructureConfigurationArn:CreateImagePipeline' :: CreateImagePipeline -> Text
$sel:name:CreateImagePipeline' :: CreateImagePipeline -> Text
$sel:tags:CreateImagePipeline' :: CreateImagePipeline -> Maybe (HashMap Text Text)
$sel:status:CreateImagePipeline' :: CreateImagePipeline -> Maybe PipelineStatus
$sel:schedule:CreateImagePipeline' :: CreateImagePipeline -> Maybe Schedule
$sel:imageTestsConfiguration:CreateImagePipeline' :: CreateImagePipeline -> Maybe ImageTestsConfiguration
$sel:imageRecipeArn:CreateImagePipeline' :: CreateImagePipeline -> Maybe Text
$sel:enhancedImageMetadataEnabled:CreateImagePipeline' :: CreateImagePipeline -> Maybe Bool
$sel:distributionConfigurationArn:CreateImagePipeline' :: CreateImagePipeline -> Maybe Text
$sel:description:CreateImagePipeline' :: CreateImagePipeline -> Maybe Text
$sel:containerRecipeArn:CreateImagePipeline' :: CreateImagePipeline -> 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
"description" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
description,
            (Key
"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
"schedule" 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 Schedule
schedule,
            (Key
"status" 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 PipelineStatus
status,
            (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
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name),
            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 CreateImagePipeline where
  toPath :: CreateImagePipeline -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/CreateImagePipeline"

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

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

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

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

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

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

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

instance Prelude.NFData CreateImagePipelineResponse where
  rnf :: CreateImagePipelineResponse -> ()
rnf CreateImagePipelineResponse' {Int
Maybe Text
httpStatus :: Int
requestId :: Maybe Text
imagePipelineArn :: Maybe Text
clientToken :: Maybe Text
$sel:httpStatus:CreateImagePipelineResponse' :: CreateImagePipelineResponse -> Int
$sel:requestId:CreateImagePipelineResponse' :: CreateImagePipelineResponse -> Maybe Text
$sel:imagePipelineArn:CreateImagePipelineResponse' :: CreateImagePipelineResponse -> Maybe Text
$sel:clientToken:CreateImagePipelineResponse' :: CreateImagePipelineResponse -> 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
imagePipelineArn
      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