{-# 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.UpdateClientCertificate
-- 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 an ClientCertificate resource.
module Amazonka.APIGateway.UpdateClientCertificate
  ( -- * Creating a Request
    UpdateClientCertificate (..),
    newUpdateClientCertificate,

    -- * Request Lenses
    updateClientCertificate_patchOperations,
    updateClientCertificate_clientCertificateId,

    -- * Destructuring the Response
    ClientCertificate (..),
    newClientCertificate,

    -- * Response Lenses
    clientCertificate_clientCertificateId,
    clientCertificate_createdDate,
    clientCertificate_description,
    clientCertificate_expirationDate,
    clientCertificate_pemEncodedCertificate,
    clientCertificate_tags,
  )
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

-- | A request to change information about an ClientCertificate resource.
--
-- /See:/ 'newUpdateClientCertificate' smart constructor.
data UpdateClientCertificate = UpdateClientCertificate'
  { -- | For more information about supported patch operations, see
    -- <https://docs.aws.amazon.com/apigateway/latest/api/patch-operations.html Patch Operations>.
    UpdateClientCertificate -> Maybe [PatchOperation]
patchOperations :: Prelude.Maybe [PatchOperation],
    -- | The identifier of the ClientCertificate resource to be updated.
    UpdateClientCertificate -> Text
clientCertificateId :: Prelude.Text
  }
  deriving (UpdateClientCertificate -> UpdateClientCertificate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateClientCertificate -> UpdateClientCertificate -> Bool
$c/= :: UpdateClientCertificate -> UpdateClientCertificate -> Bool
== :: UpdateClientCertificate -> UpdateClientCertificate -> Bool
$c== :: UpdateClientCertificate -> UpdateClientCertificate -> Bool
Prelude.Eq, ReadPrec [UpdateClientCertificate]
ReadPrec UpdateClientCertificate
Int -> ReadS UpdateClientCertificate
ReadS [UpdateClientCertificate]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateClientCertificate]
$creadListPrec :: ReadPrec [UpdateClientCertificate]
readPrec :: ReadPrec UpdateClientCertificate
$creadPrec :: ReadPrec UpdateClientCertificate
readList :: ReadS [UpdateClientCertificate]
$creadList :: ReadS [UpdateClientCertificate]
readsPrec :: Int -> ReadS UpdateClientCertificate
$creadsPrec :: Int -> ReadS UpdateClientCertificate
Prelude.Read, Int -> UpdateClientCertificate -> ShowS
[UpdateClientCertificate] -> ShowS
UpdateClientCertificate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateClientCertificate] -> ShowS
$cshowList :: [UpdateClientCertificate] -> ShowS
show :: UpdateClientCertificate -> String
$cshow :: UpdateClientCertificate -> String
showsPrec :: Int -> UpdateClientCertificate -> ShowS
$cshowsPrec :: Int -> UpdateClientCertificate -> ShowS
Prelude.Show, forall x. Rep UpdateClientCertificate x -> UpdateClientCertificate
forall x. UpdateClientCertificate -> Rep UpdateClientCertificate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateClientCertificate x -> UpdateClientCertificate
$cfrom :: forall x. UpdateClientCertificate -> Rep UpdateClientCertificate x
Prelude.Generic)

-- |
-- Create a value of 'UpdateClientCertificate' 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', 'updateClientCertificate_patchOperations' - For more information about supported patch operations, see
-- <https://docs.aws.amazon.com/apigateway/latest/api/patch-operations.html Patch Operations>.
--
-- 'clientCertificateId', 'updateClientCertificate_clientCertificateId' - The identifier of the ClientCertificate resource to be updated.
newUpdateClientCertificate ::
  -- | 'clientCertificateId'
  Prelude.Text ->
  UpdateClientCertificate
newUpdateClientCertificate :: Text -> UpdateClientCertificate
newUpdateClientCertificate Text
pClientCertificateId_ =
  UpdateClientCertificate'
    { $sel:patchOperations:UpdateClientCertificate' :: Maybe [PatchOperation]
patchOperations =
        forall a. Maybe a
Prelude.Nothing,
      $sel:clientCertificateId:UpdateClientCertificate' :: Text
clientCertificateId = Text
pClientCertificateId_
    }

-- | For more information about supported patch operations, see
-- <https://docs.aws.amazon.com/apigateway/latest/api/patch-operations.html Patch Operations>.
updateClientCertificate_patchOperations :: Lens.Lens' UpdateClientCertificate (Prelude.Maybe [PatchOperation])
updateClientCertificate_patchOperations :: Lens' UpdateClientCertificate (Maybe [PatchOperation])
updateClientCertificate_patchOperations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateClientCertificate' {Maybe [PatchOperation]
patchOperations :: Maybe [PatchOperation]
$sel:patchOperations:UpdateClientCertificate' :: UpdateClientCertificate -> Maybe [PatchOperation]
patchOperations} -> Maybe [PatchOperation]
patchOperations) (\s :: UpdateClientCertificate
s@UpdateClientCertificate' {} Maybe [PatchOperation]
a -> UpdateClientCertificate
s {$sel:patchOperations:UpdateClientCertificate' :: Maybe [PatchOperation]
patchOperations = Maybe [PatchOperation]
a} :: UpdateClientCertificate) 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 identifier of the ClientCertificate resource to be updated.
updateClientCertificate_clientCertificateId :: Lens.Lens' UpdateClientCertificate Prelude.Text
updateClientCertificate_clientCertificateId :: Lens' UpdateClientCertificate Text
updateClientCertificate_clientCertificateId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateClientCertificate' {Text
clientCertificateId :: Text
$sel:clientCertificateId:UpdateClientCertificate' :: UpdateClientCertificate -> Text
clientCertificateId} -> Text
clientCertificateId) (\s :: UpdateClientCertificate
s@UpdateClientCertificate' {} Text
a -> UpdateClientCertificate
s {$sel:clientCertificateId:UpdateClientCertificate' :: Text
clientCertificateId = Text
a} :: UpdateClientCertificate)

instance Core.AWSRequest UpdateClientCertificate where
  type
    AWSResponse UpdateClientCertificate =
      ClientCertificate
  request :: (Service -> Service)
-> UpdateClientCertificate -> Request UpdateClientCertificate
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 UpdateClientCertificate
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateClientCertificate)))
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 UpdateClientCertificate where
  hashWithSalt :: Int -> UpdateClientCertificate -> Int
hashWithSalt Int
_salt UpdateClientCertificate' {Maybe [PatchOperation]
Text
clientCertificateId :: Text
patchOperations :: Maybe [PatchOperation]
$sel:clientCertificateId:UpdateClientCertificate' :: UpdateClientCertificate -> Text
$sel:patchOperations:UpdateClientCertificate' :: UpdateClientCertificate -> 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
clientCertificateId

instance Prelude.NFData UpdateClientCertificate where
  rnf :: UpdateClientCertificate -> ()
rnf UpdateClientCertificate' {Maybe [PatchOperation]
Text
clientCertificateId :: Text
patchOperations :: Maybe [PatchOperation]
$sel:clientCertificateId:UpdateClientCertificate' :: UpdateClientCertificate -> Text
$sel:patchOperations:UpdateClientCertificate' :: UpdateClientCertificate -> 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
clientCertificateId

instance Data.ToHeaders UpdateClientCertificate where
  toHeaders :: UpdateClientCertificate -> 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 UpdateClientCertificate where
  toJSON :: UpdateClientCertificate -> Value
toJSON UpdateClientCertificate' {Maybe [PatchOperation]
Text
clientCertificateId :: Text
patchOperations :: Maybe [PatchOperation]
$sel:clientCertificateId:UpdateClientCertificate' :: UpdateClientCertificate -> Text
$sel:patchOperations:UpdateClientCertificate' :: UpdateClientCertificate -> 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 UpdateClientCertificate where
  toPath :: UpdateClientCertificate -> ByteString
toPath UpdateClientCertificate' {Maybe [PatchOperation]
Text
clientCertificateId :: Text
patchOperations :: Maybe [PatchOperation]
$sel:clientCertificateId:UpdateClientCertificate' :: UpdateClientCertificate -> Text
$sel:patchOperations:UpdateClientCertificate' :: UpdateClientCertificate -> Maybe [PatchOperation]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/clientcertificates/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
clientCertificateId
      ]

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