{-# 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.APIGateway.UpdateDeployment
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Changes information about a Deployment resource.
module Amazonka.APIGateway.UpdateDeployment
  ( -- * Creating a Request
    UpdateDeployment (..),
    newUpdateDeployment,

    -- * Request Lenses
    updateDeployment_patchOperations,
    updateDeployment_restApiId,
    updateDeployment_deploymentId,

    -- * Destructuring the Response
    Deployment (..),
    newDeployment,

    -- * Response Lenses
    deployment_apiSummary,
    deployment_createdDate,
    deployment_description,
    deployment_id,
  )
where

import Amazonka.APIGateway.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

-- | Requests API Gateway to change information about a Deployment resource.
--
-- /See:/ 'newUpdateDeployment' smart constructor.
data UpdateDeployment = UpdateDeployment'
  { -- | For more information about supported patch operations, see
    -- <https://docs.aws.amazon.com/apigateway/latest/api/patch-operations.html Patch Operations>.
    UpdateDeployment -> Maybe [PatchOperation]
patchOperations :: Prelude.Maybe [PatchOperation],
    -- | The string identifier of the associated RestApi.
    UpdateDeployment -> Text
restApiId :: Prelude.Text,
    -- | The replacement identifier for the Deployment resource to change
    -- information about.
    UpdateDeployment -> Text
deploymentId :: Prelude.Text
  }
  deriving (UpdateDeployment -> UpdateDeployment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateDeployment -> UpdateDeployment -> Bool
$c/= :: UpdateDeployment -> UpdateDeployment -> Bool
== :: UpdateDeployment -> UpdateDeployment -> Bool
$c== :: UpdateDeployment -> UpdateDeployment -> Bool
Prelude.Eq, ReadPrec [UpdateDeployment]
ReadPrec UpdateDeployment
Int -> ReadS UpdateDeployment
ReadS [UpdateDeployment]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateDeployment]
$creadListPrec :: ReadPrec [UpdateDeployment]
readPrec :: ReadPrec UpdateDeployment
$creadPrec :: ReadPrec UpdateDeployment
readList :: ReadS [UpdateDeployment]
$creadList :: ReadS [UpdateDeployment]
readsPrec :: Int -> ReadS UpdateDeployment
$creadsPrec :: Int -> ReadS UpdateDeployment
Prelude.Read, Int -> UpdateDeployment -> ShowS
[UpdateDeployment] -> ShowS
UpdateDeployment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateDeployment] -> ShowS
$cshowList :: [UpdateDeployment] -> ShowS
show :: UpdateDeployment -> String
$cshow :: UpdateDeployment -> String
showsPrec :: Int -> UpdateDeployment -> ShowS
$cshowsPrec :: Int -> UpdateDeployment -> ShowS
Prelude.Show, forall x. Rep UpdateDeployment x -> UpdateDeployment
forall x. UpdateDeployment -> Rep UpdateDeployment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateDeployment x -> UpdateDeployment
$cfrom :: forall x. UpdateDeployment -> Rep UpdateDeployment x
Prelude.Generic)

-- |
-- Create a value of 'UpdateDeployment' 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:
--
-- 'patchOperations', 'updateDeployment_patchOperations' - For more information about supported patch operations, see
-- <https://docs.aws.amazon.com/apigateway/latest/api/patch-operations.html Patch Operations>.
--
-- 'restApiId', 'updateDeployment_restApiId' - The string identifier of the associated RestApi.
--
-- 'deploymentId', 'updateDeployment_deploymentId' - The replacement identifier for the Deployment resource to change
-- information about.
newUpdateDeployment ::
  -- | 'restApiId'
  Prelude.Text ->
  -- | 'deploymentId'
  Prelude.Text ->
  UpdateDeployment
newUpdateDeployment :: Text -> Text -> UpdateDeployment
newUpdateDeployment Text
pRestApiId_ Text
pDeploymentId_ =
  UpdateDeployment'
    { $sel:patchOperations:UpdateDeployment' :: Maybe [PatchOperation]
patchOperations =
        forall a. Maybe a
Prelude.Nothing,
      $sel:restApiId:UpdateDeployment' :: Text
restApiId = Text
pRestApiId_,
      $sel:deploymentId:UpdateDeployment' :: Text
deploymentId = Text
pDeploymentId_
    }

-- | For more information about supported patch operations, see
-- <https://docs.aws.amazon.com/apigateway/latest/api/patch-operations.html Patch Operations>.
updateDeployment_patchOperations :: Lens.Lens' UpdateDeployment (Prelude.Maybe [PatchOperation])
updateDeployment_patchOperations :: Lens' UpdateDeployment (Maybe [PatchOperation])
updateDeployment_patchOperations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDeployment' {Maybe [PatchOperation]
patchOperations :: Maybe [PatchOperation]
$sel:patchOperations:UpdateDeployment' :: UpdateDeployment -> Maybe [PatchOperation]
patchOperations} -> Maybe [PatchOperation]
patchOperations) (\s :: UpdateDeployment
s@UpdateDeployment' {} Maybe [PatchOperation]
a -> UpdateDeployment
s {$sel:patchOperations:UpdateDeployment' :: Maybe [PatchOperation]
patchOperations = Maybe [PatchOperation]
a} :: UpdateDeployment) 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 string identifier of the associated RestApi.
updateDeployment_restApiId :: Lens.Lens' UpdateDeployment Prelude.Text
updateDeployment_restApiId :: Lens' UpdateDeployment Text
updateDeployment_restApiId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDeployment' {Text
restApiId :: Text
$sel:restApiId:UpdateDeployment' :: UpdateDeployment -> Text
restApiId} -> Text
restApiId) (\s :: UpdateDeployment
s@UpdateDeployment' {} Text
a -> UpdateDeployment
s {$sel:restApiId:UpdateDeployment' :: Text
restApiId = Text
a} :: UpdateDeployment)

-- | The replacement identifier for the Deployment resource to change
-- information about.
updateDeployment_deploymentId :: Lens.Lens' UpdateDeployment Prelude.Text
updateDeployment_deploymentId :: Lens' UpdateDeployment Text
updateDeployment_deploymentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDeployment' {Text
deploymentId :: Text
$sel:deploymentId:UpdateDeployment' :: UpdateDeployment -> Text
deploymentId} -> Text
deploymentId) (\s :: UpdateDeployment
s@UpdateDeployment' {} Text
a -> UpdateDeployment
s {$sel:deploymentId:UpdateDeployment' :: Text
deploymentId = Text
a} :: UpdateDeployment)

instance Core.AWSRequest UpdateDeployment where
  type AWSResponse UpdateDeployment = Deployment
  request :: (Service -> Service)
-> UpdateDeployment -> Request UpdateDeployment
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.patchJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateDeployment
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateDeployment)))
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 -> forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)

instance Prelude.Hashable UpdateDeployment where
  hashWithSalt :: Int -> UpdateDeployment -> Int
hashWithSalt Int
_salt UpdateDeployment' {Maybe [PatchOperation]
Text
deploymentId :: Text
restApiId :: Text
patchOperations :: Maybe [PatchOperation]
$sel:deploymentId:UpdateDeployment' :: UpdateDeployment -> Text
$sel:restApiId:UpdateDeployment' :: UpdateDeployment -> Text
$sel:patchOperations:UpdateDeployment' :: UpdateDeployment -> Maybe [PatchOperation]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [PatchOperation]
patchOperations
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
restApiId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
deploymentId

instance Prelude.NFData UpdateDeployment where
  rnf :: UpdateDeployment -> ()
rnf UpdateDeployment' {Maybe [PatchOperation]
Text
deploymentId :: Text
restApiId :: Text
patchOperations :: Maybe [PatchOperation]
$sel:deploymentId:UpdateDeployment' :: UpdateDeployment -> Text
$sel:restApiId:UpdateDeployment' :: UpdateDeployment -> Text
$sel:patchOperations:UpdateDeployment' :: UpdateDeployment -> Maybe [PatchOperation]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [PatchOperation]
patchOperations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
restApiId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
deploymentId

instance Data.ToHeaders UpdateDeployment where
  toHeaders :: UpdateDeployment -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Accept"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# (ByteString
"application/json" :: Prelude.ByteString)
          ]
      )

instance Data.ToJSON UpdateDeployment where
  toJSON :: UpdateDeployment -> Value
toJSON UpdateDeployment' {Maybe [PatchOperation]
Text
deploymentId :: Text
restApiId :: Text
patchOperations :: Maybe [PatchOperation]
$sel:deploymentId:UpdateDeployment' :: UpdateDeployment -> Text
$sel:restApiId:UpdateDeployment' :: UpdateDeployment -> Text
$sel:patchOperations:UpdateDeployment' :: UpdateDeployment -> Maybe [PatchOperation]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"patchOperations" 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 [PatchOperation]
patchOperations
          ]
      )

instance Data.ToPath UpdateDeployment where
  toPath :: UpdateDeployment -> ByteString
toPath UpdateDeployment' {Maybe [PatchOperation]
Text
deploymentId :: Text
restApiId :: Text
patchOperations :: Maybe [PatchOperation]
$sel:deploymentId:UpdateDeployment' :: UpdateDeployment -> Text
$sel:restApiId:UpdateDeployment' :: UpdateDeployment -> Text
$sel:patchOperations:UpdateDeployment' :: UpdateDeployment -> Maybe [PatchOperation]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/restapis/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
restApiId,
        ByteString
"/deployments/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
deploymentId
      ]

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