{-# 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.CodePipeline.UpdatePipeline
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates a specified pipeline with edits or changes to its structure. Use
-- a JSON file with the pipeline structure and @UpdatePipeline@ to provide
-- the full structure of the pipeline. Updating the pipeline increases the
-- version number of the pipeline by 1.
module Amazonka.CodePipeline.UpdatePipeline
  ( -- * Creating a Request
    UpdatePipeline (..),
    newUpdatePipeline,

    -- * Request Lenses
    updatePipeline_pipeline,

    -- * Destructuring the Response
    UpdatePipelineResponse (..),
    newUpdatePipelineResponse,

    -- * Response Lenses
    updatePipelineResponse_pipeline,
    updatePipelineResponse_httpStatus,
  )
where

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

-- | Represents the input of an @UpdatePipeline@ action.
--
-- /See:/ 'newUpdatePipeline' smart constructor.
data UpdatePipeline = UpdatePipeline'
  { -- | The name of the pipeline to be updated.
    UpdatePipeline -> PipelineDeclaration
pipeline :: PipelineDeclaration
  }
  deriving (UpdatePipeline -> UpdatePipeline -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdatePipeline -> UpdatePipeline -> Bool
$c/= :: UpdatePipeline -> UpdatePipeline -> Bool
== :: UpdatePipeline -> UpdatePipeline -> Bool
$c== :: UpdatePipeline -> UpdatePipeline -> Bool
Prelude.Eq, ReadPrec [UpdatePipeline]
ReadPrec UpdatePipeline
Int -> ReadS UpdatePipeline
ReadS [UpdatePipeline]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdatePipeline]
$creadListPrec :: ReadPrec [UpdatePipeline]
readPrec :: ReadPrec UpdatePipeline
$creadPrec :: ReadPrec UpdatePipeline
readList :: ReadS [UpdatePipeline]
$creadList :: ReadS [UpdatePipeline]
readsPrec :: Int -> ReadS UpdatePipeline
$creadsPrec :: Int -> ReadS UpdatePipeline
Prelude.Read, Int -> UpdatePipeline -> ShowS
[UpdatePipeline] -> ShowS
UpdatePipeline -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdatePipeline] -> ShowS
$cshowList :: [UpdatePipeline] -> ShowS
show :: UpdatePipeline -> String
$cshow :: UpdatePipeline -> String
showsPrec :: Int -> UpdatePipeline -> ShowS
$cshowsPrec :: Int -> UpdatePipeline -> ShowS
Prelude.Show, forall x. Rep UpdatePipeline x -> UpdatePipeline
forall x. UpdatePipeline -> Rep UpdatePipeline x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdatePipeline x -> UpdatePipeline
$cfrom :: forall x. UpdatePipeline -> Rep UpdatePipeline x
Prelude.Generic)

-- |
-- Create a value of 'UpdatePipeline' 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:
--
-- 'pipeline', 'updatePipeline_pipeline' - The name of the pipeline to be updated.
newUpdatePipeline ::
  -- | 'pipeline'
  PipelineDeclaration ->
  UpdatePipeline
newUpdatePipeline :: PipelineDeclaration -> UpdatePipeline
newUpdatePipeline PipelineDeclaration
pPipeline_ =
  UpdatePipeline' {$sel:pipeline:UpdatePipeline' :: PipelineDeclaration
pipeline = PipelineDeclaration
pPipeline_}

-- | The name of the pipeline to be updated.
updatePipeline_pipeline :: Lens.Lens' UpdatePipeline PipelineDeclaration
updatePipeline_pipeline :: Lens' UpdatePipeline PipelineDeclaration
updatePipeline_pipeline = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePipeline' {PipelineDeclaration
pipeline :: PipelineDeclaration
$sel:pipeline:UpdatePipeline' :: UpdatePipeline -> PipelineDeclaration
pipeline} -> PipelineDeclaration
pipeline) (\s :: UpdatePipeline
s@UpdatePipeline' {} PipelineDeclaration
a -> UpdatePipeline
s {$sel:pipeline:UpdatePipeline' :: PipelineDeclaration
pipeline = PipelineDeclaration
a} :: UpdatePipeline)

instance Core.AWSRequest UpdatePipeline where
  type
    AWSResponse UpdatePipeline =
      UpdatePipelineResponse
  request :: (Service -> Service) -> UpdatePipeline -> Request UpdatePipeline
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdatePipeline
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdatePipeline)))
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 PipelineDeclaration -> Int -> UpdatePipelineResponse
UpdatePipelineResponse'
            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
"pipeline")
            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 UpdatePipeline where
  hashWithSalt :: Int -> UpdatePipeline -> Int
hashWithSalt Int
_salt UpdatePipeline' {PipelineDeclaration
pipeline :: PipelineDeclaration
$sel:pipeline:UpdatePipeline' :: UpdatePipeline -> PipelineDeclaration
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` PipelineDeclaration
pipeline

instance Prelude.NFData UpdatePipeline where
  rnf :: UpdatePipeline -> ()
rnf UpdatePipeline' {PipelineDeclaration
pipeline :: PipelineDeclaration
$sel:pipeline:UpdatePipeline' :: UpdatePipeline -> PipelineDeclaration
..} = forall a. NFData a => a -> ()
Prelude.rnf PipelineDeclaration
pipeline

instance Data.ToHeaders UpdatePipeline where
  toHeaders :: UpdatePipeline -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"CodePipeline_20150709.UpdatePipeline" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdatePipeline where
  toJSON :: UpdatePipeline -> Value
toJSON UpdatePipeline' {PipelineDeclaration
pipeline :: PipelineDeclaration
$sel:pipeline:UpdatePipeline' :: UpdatePipeline -> PipelineDeclaration
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"pipeline" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= PipelineDeclaration
pipeline)]
      )

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

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

-- | Represents the output of an @UpdatePipeline@ action.
--
-- /See:/ 'newUpdatePipelineResponse' smart constructor.
data UpdatePipelineResponse = UpdatePipelineResponse'
  { -- | The structure of the updated pipeline.
    UpdatePipelineResponse -> Maybe PipelineDeclaration
pipeline :: Prelude.Maybe PipelineDeclaration,
    -- | The response's http status code.
    UpdatePipelineResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdatePipelineResponse -> UpdatePipelineResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdatePipelineResponse -> UpdatePipelineResponse -> Bool
$c/= :: UpdatePipelineResponse -> UpdatePipelineResponse -> Bool
== :: UpdatePipelineResponse -> UpdatePipelineResponse -> Bool
$c== :: UpdatePipelineResponse -> UpdatePipelineResponse -> Bool
Prelude.Eq, ReadPrec [UpdatePipelineResponse]
ReadPrec UpdatePipelineResponse
Int -> ReadS UpdatePipelineResponse
ReadS [UpdatePipelineResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdatePipelineResponse]
$creadListPrec :: ReadPrec [UpdatePipelineResponse]
readPrec :: ReadPrec UpdatePipelineResponse
$creadPrec :: ReadPrec UpdatePipelineResponse
readList :: ReadS [UpdatePipelineResponse]
$creadList :: ReadS [UpdatePipelineResponse]
readsPrec :: Int -> ReadS UpdatePipelineResponse
$creadsPrec :: Int -> ReadS UpdatePipelineResponse
Prelude.Read, Int -> UpdatePipelineResponse -> ShowS
[UpdatePipelineResponse] -> ShowS
UpdatePipelineResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdatePipelineResponse] -> ShowS
$cshowList :: [UpdatePipelineResponse] -> ShowS
show :: UpdatePipelineResponse -> String
$cshow :: UpdatePipelineResponse -> String
showsPrec :: Int -> UpdatePipelineResponse -> ShowS
$cshowsPrec :: Int -> UpdatePipelineResponse -> ShowS
Prelude.Show, forall x. Rep UpdatePipelineResponse x -> UpdatePipelineResponse
forall x. UpdatePipelineResponse -> Rep UpdatePipelineResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdatePipelineResponse x -> UpdatePipelineResponse
$cfrom :: forall x. UpdatePipelineResponse -> Rep UpdatePipelineResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdatePipelineResponse' 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:
--
-- 'pipeline', 'updatePipelineResponse_pipeline' - The structure of the updated pipeline.
--
-- 'httpStatus', 'updatePipelineResponse_httpStatus' - The response's http status code.
newUpdatePipelineResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdatePipelineResponse
newUpdatePipelineResponse :: Int -> UpdatePipelineResponse
newUpdatePipelineResponse Int
pHttpStatus_ =
  UpdatePipelineResponse'
    { $sel:pipeline:UpdatePipelineResponse' :: Maybe PipelineDeclaration
pipeline = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdatePipelineResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The structure of the updated pipeline.
updatePipelineResponse_pipeline :: Lens.Lens' UpdatePipelineResponse (Prelude.Maybe PipelineDeclaration)
updatePipelineResponse_pipeline :: Lens' UpdatePipelineResponse (Maybe PipelineDeclaration)
updatePipelineResponse_pipeline = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdatePipelineResponse' {Maybe PipelineDeclaration
pipeline :: Maybe PipelineDeclaration
$sel:pipeline:UpdatePipelineResponse' :: UpdatePipelineResponse -> Maybe PipelineDeclaration
pipeline} -> Maybe PipelineDeclaration
pipeline) (\s :: UpdatePipelineResponse
s@UpdatePipelineResponse' {} Maybe PipelineDeclaration
a -> UpdatePipelineResponse
s {$sel:pipeline:UpdatePipelineResponse' :: Maybe PipelineDeclaration
pipeline = Maybe PipelineDeclaration
a} :: UpdatePipelineResponse)

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

instance Prelude.NFData UpdatePipelineResponse where
  rnf :: UpdatePipelineResponse -> ()
rnf UpdatePipelineResponse' {Int
Maybe PipelineDeclaration
httpStatus :: Int
pipeline :: Maybe PipelineDeclaration
$sel:httpStatus:UpdatePipelineResponse' :: UpdatePipelineResponse -> Int
$sel:pipeline:UpdatePipelineResponse' :: UpdatePipelineResponse -> Maybe PipelineDeclaration
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe PipelineDeclaration
pipeline
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus