{-# 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.StartImagePipelineExecution
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Manually triggers a pipeline to create an image.
module Amazonka.ImageBuilder.StartImagePipelineExecution
  ( -- * Creating a Request
    StartImagePipelineExecution (..),
    newStartImagePipelineExecution,

    -- * Request Lenses
    startImagePipelineExecution_imagePipelineArn,
    startImagePipelineExecution_clientToken,

    -- * Destructuring the Response
    StartImagePipelineExecutionResponse (..),
    newStartImagePipelineExecutionResponse,

    -- * Response Lenses
    startImagePipelineExecutionResponse_clientToken,
    startImagePipelineExecutionResponse_imageBuildVersionArn,
    startImagePipelineExecutionResponse_requestId,
    startImagePipelineExecutionResponse_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:/ 'newStartImagePipelineExecution' smart constructor.
data StartImagePipelineExecution = StartImagePipelineExecution'
  { -- | The Amazon Resource Name (ARN) of the image pipeline that you want to
    -- manually invoke.
    StartImagePipelineExecution -> Text
imagePipelineArn :: Prelude.Text,
    -- | The idempotency token used to make this request idempotent.
    StartImagePipelineExecution -> Text
clientToken :: Prelude.Text
  }
  deriving (StartImagePipelineExecution -> StartImagePipelineExecution -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartImagePipelineExecution -> StartImagePipelineExecution -> Bool
$c/= :: StartImagePipelineExecution -> StartImagePipelineExecution -> Bool
== :: StartImagePipelineExecution -> StartImagePipelineExecution -> Bool
$c== :: StartImagePipelineExecution -> StartImagePipelineExecution -> Bool
Prelude.Eq, ReadPrec [StartImagePipelineExecution]
ReadPrec StartImagePipelineExecution
Int -> ReadS StartImagePipelineExecution
ReadS [StartImagePipelineExecution]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartImagePipelineExecution]
$creadListPrec :: ReadPrec [StartImagePipelineExecution]
readPrec :: ReadPrec StartImagePipelineExecution
$creadPrec :: ReadPrec StartImagePipelineExecution
readList :: ReadS [StartImagePipelineExecution]
$creadList :: ReadS [StartImagePipelineExecution]
readsPrec :: Int -> ReadS StartImagePipelineExecution
$creadsPrec :: Int -> ReadS StartImagePipelineExecution
Prelude.Read, Int -> StartImagePipelineExecution -> ShowS
[StartImagePipelineExecution] -> ShowS
StartImagePipelineExecution -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartImagePipelineExecution] -> ShowS
$cshowList :: [StartImagePipelineExecution] -> ShowS
show :: StartImagePipelineExecution -> String
$cshow :: StartImagePipelineExecution -> String
showsPrec :: Int -> StartImagePipelineExecution -> ShowS
$cshowsPrec :: Int -> StartImagePipelineExecution -> ShowS
Prelude.Show, forall x.
Rep StartImagePipelineExecution x -> StartImagePipelineExecution
forall x.
StartImagePipelineExecution -> Rep StartImagePipelineExecution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StartImagePipelineExecution x -> StartImagePipelineExecution
$cfrom :: forall x.
StartImagePipelineExecution -> Rep StartImagePipelineExecution x
Prelude.Generic)

-- |
-- Create a value of 'StartImagePipelineExecution' 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:
--
-- 'imagePipelineArn', 'startImagePipelineExecution_imagePipelineArn' - The Amazon Resource Name (ARN) of the image pipeline that you want to
-- manually invoke.
--
-- 'clientToken', 'startImagePipelineExecution_clientToken' - The idempotency token used to make this request idempotent.
newStartImagePipelineExecution ::
  -- | 'imagePipelineArn'
  Prelude.Text ->
  -- | 'clientToken'
  Prelude.Text ->
  StartImagePipelineExecution
newStartImagePipelineExecution :: Text -> Text -> StartImagePipelineExecution
newStartImagePipelineExecution
  Text
pImagePipelineArn_
  Text
pClientToken_ =
    StartImagePipelineExecution'
      { $sel:imagePipelineArn:StartImagePipelineExecution' :: Text
imagePipelineArn =
          Text
pImagePipelineArn_,
        $sel:clientToken:StartImagePipelineExecution' :: Text
clientToken = Text
pClientToken_
      }

-- | The Amazon Resource Name (ARN) of the image pipeline that you want to
-- manually invoke.
startImagePipelineExecution_imagePipelineArn :: Lens.Lens' StartImagePipelineExecution Prelude.Text
startImagePipelineExecution_imagePipelineArn :: Lens' StartImagePipelineExecution Text
startImagePipelineExecution_imagePipelineArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImagePipelineExecution' {Text
imagePipelineArn :: Text
$sel:imagePipelineArn:StartImagePipelineExecution' :: StartImagePipelineExecution -> Text
imagePipelineArn} -> Text
imagePipelineArn) (\s :: StartImagePipelineExecution
s@StartImagePipelineExecution' {} Text
a -> StartImagePipelineExecution
s {$sel:imagePipelineArn:StartImagePipelineExecution' :: Text
imagePipelineArn = Text
a} :: StartImagePipelineExecution)

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

instance Core.AWSRequest StartImagePipelineExecution where
  type
    AWSResponse StartImagePipelineExecution =
      StartImagePipelineExecutionResponse
  request :: (Service -> Service)
-> StartImagePipelineExecution
-> Request StartImagePipelineExecution
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 StartImagePipelineExecution
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StartImagePipelineExecution)))
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
-> StartImagePipelineExecutionResponse
StartImagePipelineExecutionResponse'
            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 StartImagePipelineExecution where
  hashWithSalt :: Int -> StartImagePipelineExecution -> Int
hashWithSalt Int
_salt StartImagePipelineExecution' {Text
clientToken :: Text
imagePipelineArn :: Text
$sel:clientToken:StartImagePipelineExecution' :: StartImagePipelineExecution -> Text
$sel:imagePipelineArn:StartImagePipelineExecution' :: StartImagePipelineExecution -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
imagePipelineArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clientToken

instance Prelude.NFData StartImagePipelineExecution where
  rnf :: StartImagePipelineExecution -> ()
rnf StartImagePipelineExecution' {Text
clientToken :: Text
imagePipelineArn :: Text
$sel:clientToken:StartImagePipelineExecution' :: StartImagePipelineExecution -> Text
$sel:imagePipelineArn:StartImagePipelineExecution' :: StartImagePipelineExecution -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
imagePipelineArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
clientToken

instance Data.ToHeaders StartImagePipelineExecution where
  toHeaders :: StartImagePipelineExecution -> 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 StartImagePipelineExecution where
  toJSON :: StartImagePipelineExecution -> Value
toJSON StartImagePipelineExecution' {Text
clientToken :: Text
imagePipelineArn :: Text
$sel:clientToken:StartImagePipelineExecution' :: StartImagePipelineExecution -> Text
$sel:imagePipelineArn:StartImagePipelineExecution' :: StartImagePipelineExecution -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"imagePipelineArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
imagePipelineArn),
            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 StartImagePipelineExecution where
  toPath :: StartImagePipelineExecution -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/StartImagePipelineExecution"

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

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

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

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

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

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

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

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