{-# 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.KMS.UpdateKeyDescription
-- 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 the description of a KMS key. To see the description of a KMS
-- key, use DescribeKey.
--
-- The KMS key that you use for this operation must be in a compatible key
-- state. For details, see
-- <https://docs.aws.amazon.com/kms/latest/developerguide/key-state.html Key states of KMS keys>
-- in the /Key Management Service Developer Guide/.
--
-- __Cross-account use__: No. You cannot perform this operation on a KMS
-- key in a different Amazon Web Services account.
--
-- __Required permissions__:
-- <https://docs.aws.amazon.com/kms/latest/developerguide/kms-api-permissions-reference.html kms:UpdateKeyDescription>
-- (key policy)
--
-- __Related operations__
--
-- -   CreateKey
--
-- -   DescribeKey
module Amazonka.KMS.UpdateKeyDescription
  ( -- * Creating a Request
    UpdateKeyDescription (..),
    newUpdateKeyDescription,

    -- * Request Lenses
    updateKeyDescription_keyId,
    updateKeyDescription_description,

    -- * Destructuring the Response
    UpdateKeyDescriptionResponse (..),
    newUpdateKeyDescriptionResponse,
  )
where

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

-- | /See:/ 'newUpdateKeyDescription' smart constructor.
data UpdateKeyDescription = UpdateKeyDescription'
  { -- | Updates the description of the specified KMS key.
    --
    -- Specify the key ID or key ARN of the KMS key.
    --
    -- For example:
    --
    -- -   Key ID: @1234abcd-12ab-34cd-56ef-1234567890ab@
    --
    -- -   Key ARN:
    --     @arn:aws:kms:us-east-2:111122223333:key\/1234abcd-12ab-34cd-56ef-1234567890ab@
    --
    -- To get the key ID and key ARN for a KMS key, use ListKeys or
    -- DescribeKey.
    UpdateKeyDescription -> Text
keyId :: Prelude.Text,
    -- | New description for the KMS key.
    UpdateKeyDescription -> Text
description :: Prelude.Text
  }
  deriving (UpdateKeyDescription -> UpdateKeyDescription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateKeyDescription -> UpdateKeyDescription -> Bool
$c/= :: UpdateKeyDescription -> UpdateKeyDescription -> Bool
== :: UpdateKeyDescription -> UpdateKeyDescription -> Bool
$c== :: UpdateKeyDescription -> UpdateKeyDescription -> Bool
Prelude.Eq, ReadPrec [UpdateKeyDescription]
ReadPrec UpdateKeyDescription
Int -> ReadS UpdateKeyDescription
ReadS [UpdateKeyDescription]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateKeyDescription]
$creadListPrec :: ReadPrec [UpdateKeyDescription]
readPrec :: ReadPrec UpdateKeyDescription
$creadPrec :: ReadPrec UpdateKeyDescription
readList :: ReadS [UpdateKeyDescription]
$creadList :: ReadS [UpdateKeyDescription]
readsPrec :: Int -> ReadS UpdateKeyDescription
$creadsPrec :: Int -> ReadS UpdateKeyDescription
Prelude.Read, Int -> UpdateKeyDescription -> ShowS
[UpdateKeyDescription] -> ShowS
UpdateKeyDescription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateKeyDescription] -> ShowS
$cshowList :: [UpdateKeyDescription] -> ShowS
show :: UpdateKeyDescription -> String
$cshow :: UpdateKeyDescription -> String
showsPrec :: Int -> UpdateKeyDescription -> ShowS
$cshowsPrec :: Int -> UpdateKeyDescription -> ShowS
Prelude.Show, forall x. Rep UpdateKeyDescription x -> UpdateKeyDescription
forall x. UpdateKeyDescription -> Rep UpdateKeyDescription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateKeyDescription x -> UpdateKeyDescription
$cfrom :: forall x. UpdateKeyDescription -> Rep UpdateKeyDescription x
Prelude.Generic)

-- |
-- Create a value of 'UpdateKeyDescription' 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:
--
-- 'keyId', 'updateKeyDescription_keyId' - Updates the description of the specified KMS key.
--
-- Specify the key ID or key ARN of the KMS key.
--
-- For example:
--
-- -   Key ID: @1234abcd-12ab-34cd-56ef-1234567890ab@
--
-- -   Key ARN:
--     @arn:aws:kms:us-east-2:111122223333:key\/1234abcd-12ab-34cd-56ef-1234567890ab@
--
-- To get the key ID and key ARN for a KMS key, use ListKeys or
-- DescribeKey.
--
-- 'description', 'updateKeyDescription_description' - New description for the KMS key.
newUpdateKeyDescription ::
  -- | 'keyId'
  Prelude.Text ->
  -- | 'description'
  Prelude.Text ->
  UpdateKeyDescription
newUpdateKeyDescription :: Text -> Text -> UpdateKeyDescription
newUpdateKeyDescription Text
pKeyId_ Text
pDescription_ =
  UpdateKeyDescription'
    { $sel:keyId:UpdateKeyDescription' :: Text
keyId = Text
pKeyId_,
      $sel:description:UpdateKeyDescription' :: Text
description = Text
pDescription_
    }

-- | Updates the description of the specified KMS key.
--
-- Specify the key ID or key ARN of the KMS key.
--
-- For example:
--
-- -   Key ID: @1234abcd-12ab-34cd-56ef-1234567890ab@
--
-- -   Key ARN:
--     @arn:aws:kms:us-east-2:111122223333:key\/1234abcd-12ab-34cd-56ef-1234567890ab@
--
-- To get the key ID and key ARN for a KMS key, use ListKeys or
-- DescribeKey.
updateKeyDescription_keyId :: Lens.Lens' UpdateKeyDescription Prelude.Text
updateKeyDescription_keyId :: Lens' UpdateKeyDescription Text
updateKeyDescription_keyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateKeyDescription' {Text
keyId :: Text
$sel:keyId:UpdateKeyDescription' :: UpdateKeyDescription -> Text
keyId} -> Text
keyId) (\s :: UpdateKeyDescription
s@UpdateKeyDescription' {} Text
a -> UpdateKeyDescription
s {$sel:keyId:UpdateKeyDescription' :: Text
keyId = Text
a} :: UpdateKeyDescription)

-- | New description for the KMS key.
updateKeyDescription_description :: Lens.Lens' UpdateKeyDescription Prelude.Text
updateKeyDescription_description :: Lens' UpdateKeyDescription Text
updateKeyDescription_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateKeyDescription' {Text
description :: Text
$sel:description:UpdateKeyDescription' :: UpdateKeyDescription -> Text
description} -> Text
description) (\s :: UpdateKeyDescription
s@UpdateKeyDescription' {} Text
a -> UpdateKeyDescription
s {$sel:description:UpdateKeyDescription' :: Text
description = Text
a} :: UpdateKeyDescription)

instance Core.AWSRequest UpdateKeyDescription where
  type
    AWSResponse UpdateKeyDescription =
      UpdateKeyDescriptionResponse
  request :: (Service -> Service)
-> UpdateKeyDescription -> Request UpdateKeyDescription
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 UpdateKeyDescription
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateKeyDescription)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull UpdateKeyDescriptionResponse
UpdateKeyDescriptionResponse'

instance Prelude.Hashable UpdateKeyDescription where
  hashWithSalt :: Int -> UpdateKeyDescription -> Int
hashWithSalt Int
_salt UpdateKeyDescription' {Text
description :: Text
keyId :: Text
$sel:description:UpdateKeyDescription' :: UpdateKeyDescription -> Text
$sel:keyId:UpdateKeyDescription' :: UpdateKeyDescription -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
keyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
description

instance Prelude.NFData UpdateKeyDescription where
  rnf :: UpdateKeyDescription -> ()
rnf UpdateKeyDescription' {Text
description :: Text
keyId :: Text
$sel:description:UpdateKeyDescription' :: UpdateKeyDescription -> Text
$sel:keyId:UpdateKeyDescription' :: UpdateKeyDescription -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
keyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
description

instance Data.ToHeaders UpdateKeyDescription where
  toHeaders :: UpdateKeyDescription -> [Header]
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 -> [Header]
Data.=# ( ByteString
"TrentService.UpdateKeyDescription" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateKeyDescription where
  toJSON :: UpdateKeyDescription -> Value
toJSON UpdateKeyDescription' {Text
description :: Text
keyId :: Text
$sel:description:UpdateKeyDescription' :: UpdateKeyDescription -> Text
$sel:keyId:UpdateKeyDescription' :: UpdateKeyDescription -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"KeyId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
keyId),
            forall a. a -> Maybe a
Prelude.Just (Key
"Description" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
description)
          ]
      )

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

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

-- | /See:/ 'newUpdateKeyDescriptionResponse' smart constructor.
data UpdateKeyDescriptionResponse = UpdateKeyDescriptionResponse'
  {
  }
  deriving (UpdateKeyDescriptionResponse
-> UpdateKeyDescriptionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateKeyDescriptionResponse
-> UpdateKeyDescriptionResponse -> Bool
$c/= :: UpdateKeyDescriptionResponse
-> UpdateKeyDescriptionResponse -> Bool
== :: UpdateKeyDescriptionResponse
-> UpdateKeyDescriptionResponse -> Bool
$c== :: UpdateKeyDescriptionResponse
-> UpdateKeyDescriptionResponse -> Bool
Prelude.Eq, ReadPrec [UpdateKeyDescriptionResponse]
ReadPrec UpdateKeyDescriptionResponse
Int -> ReadS UpdateKeyDescriptionResponse
ReadS [UpdateKeyDescriptionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateKeyDescriptionResponse]
$creadListPrec :: ReadPrec [UpdateKeyDescriptionResponse]
readPrec :: ReadPrec UpdateKeyDescriptionResponse
$creadPrec :: ReadPrec UpdateKeyDescriptionResponse
readList :: ReadS [UpdateKeyDescriptionResponse]
$creadList :: ReadS [UpdateKeyDescriptionResponse]
readsPrec :: Int -> ReadS UpdateKeyDescriptionResponse
$creadsPrec :: Int -> ReadS UpdateKeyDescriptionResponse
Prelude.Read, Int -> UpdateKeyDescriptionResponse -> ShowS
[UpdateKeyDescriptionResponse] -> ShowS
UpdateKeyDescriptionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateKeyDescriptionResponse] -> ShowS
$cshowList :: [UpdateKeyDescriptionResponse] -> ShowS
show :: UpdateKeyDescriptionResponse -> String
$cshow :: UpdateKeyDescriptionResponse -> String
showsPrec :: Int -> UpdateKeyDescriptionResponse -> ShowS
$cshowsPrec :: Int -> UpdateKeyDescriptionResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateKeyDescriptionResponse x -> UpdateKeyDescriptionResponse
forall x.
UpdateKeyDescriptionResponse -> Rep UpdateKeyDescriptionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateKeyDescriptionResponse x -> UpdateKeyDescriptionResponse
$cfrom :: forall x.
UpdateKeyDescriptionResponse -> Rep UpdateKeyDescriptionResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateKeyDescriptionResponse' 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.
newUpdateKeyDescriptionResponse ::
  UpdateKeyDescriptionResponse
newUpdateKeyDescriptionResponse :: UpdateKeyDescriptionResponse
newUpdateKeyDescriptionResponse =
  UpdateKeyDescriptionResponse
UpdateKeyDescriptionResponse'

instance Prelude.NFData UpdateKeyDescriptionResponse where
  rnf :: UpdateKeyDescriptionResponse -> ()
rnf UpdateKeyDescriptionResponse
_ = ()