{-# 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.DeleteImportedKeyMaterial
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes key material that you previously imported. This operation makes
-- the specified KMS key unusable. For more information about importing key
-- material into KMS, see
-- <https://docs.aws.amazon.com/kms/latest/developerguide/importing-keys.html Importing Key Material>
-- in the /Key Management Service Developer Guide/.
--
-- When the specified KMS key is in the @PendingDeletion@ state, this
-- operation does not change the KMS key\'s state. Otherwise, it changes
-- the KMS key\'s state to @PendingImport@.
--
-- After you delete key material, you can use ImportKeyMaterial to reimport
-- the same key material into the KMS key.
--
-- 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:DeleteImportedKeyMaterial>
-- (key policy)
--
-- __Related operations:__
--
-- -   GetParametersForImport
--
-- -   ImportKeyMaterial
module Amazonka.KMS.DeleteImportedKeyMaterial
  ( -- * Creating a Request
    DeleteImportedKeyMaterial (..),
    newDeleteImportedKeyMaterial,

    -- * Request Lenses
    deleteImportedKeyMaterial_keyId,

    -- * Destructuring the Response
    DeleteImportedKeyMaterialResponse (..),
    newDeleteImportedKeyMaterialResponse,
  )
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:/ 'newDeleteImportedKeyMaterial' smart constructor.
data DeleteImportedKeyMaterial = DeleteImportedKeyMaterial'
  { -- | Identifies the KMS key from which you are deleting imported key
    -- material. The @Origin@ of the KMS key must be @EXTERNAL@.
    --
    -- 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.
    DeleteImportedKeyMaterial -> Text
keyId :: Prelude.Text
  }
  deriving (DeleteImportedKeyMaterial -> DeleteImportedKeyMaterial -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteImportedKeyMaterial -> DeleteImportedKeyMaterial -> Bool
$c/= :: DeleteImportedKeyMaterial -> DeleteImportedKeyMaterial -> Bool
== :: DeleteImportedKeyMaterial -> DeleteImportedKeyMaterial -> Bool
$c== :: DeleteImportedKeyMaterial -> DeleteImportedKeyMaterial -> Bool
Prelude.Eq, ReadPrec [DeleteImportedKeyMaterial]
ReadPrec DeleteImportedKeyMaterial
Int -> ReadS DeleteImportedKeyMaterial
ReadS [DeleteImportedKeyMaterial]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteImportedKeyMaterial]
$creadListPrec :: ReadPrec [DeleteImportedKeyMaterial]
readPrec :: ReadPrec DeleteImportedKeyMaterial
$creadPrec :: ReadPrec DeleteImportedKeyMaterial
readList :: ReadS [DeleteImportedKeyMaterial]
$creadList :: ReadS [DeleteImportedKeyMaterial]
readsPrec :: Int -> ReadS DeleteImportedKeyMaterial
$creadsPrec :: Int -> ReadS DeleteImportedKeyMaterial
Prelude.Read, Int -> DeleteImportedKeyMaterial -> ShowS
[DeleteImportedKeyMaterial] -> ShowS
DeleteImportedKeyMaterial -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteImportedKeyMaterial] -> ShowS
$cshowList :: [DeleteImportedKeyMaterial] -> ShowS
show :: DeleteImportedKeyMaterial -> String
$cshow :: DeleteImportedKeyMaterial -> String
showsPrec :: Int -> DeleteImportedKeyMaterial -> ShowS
$cshowsPrec :: Int -> DeleteImportedKeyMaterial -> ShowS
Prelude.Show, forall x.
Rep DeleteImportedKeyMaterial x -> DeleteImportedKeyMaterial
forall x.
DeleteImportedKeyMaterial -> Rep DeleteImportedKeyMaterial x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteImportedKeyMaterial x -> DeleteImportedKeyMaterial
$cfrom :: forall x.
DeleteImportedKeyMaterial -> Rep DeleteImportedKeyMaterial x
Prelude.Generic)

-- |
-- Create a value of 'DeleteImportedKeyMaterial' 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', 'deleteImportedKeyMaterial_keyId' - Identifies the KMS key from which you are deleting imported key
-- material. The @Origin@ of the KMS key must be @EXTERNAL@.
--
-- 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.
newDeleteImportedKeyMaterial ::
  -- | 'keyId'
  Prelude.Text ->
  DeleteImportedKeyMaterial
newDeleteImportedKeyMaterial :: Text -> DeleteImportedKeyMaterial
newDeleteImportedKeyMaterial Text
pKeyId_ =
  DeleteImportedKeyMaterial' {$sel:keyId:DeleteImportedKeyMaterial' :: Text
keyId = Text
pKeyId_}

-- | Identifies the KMS key from which you are deleting imported key
-- material. The @Origin@ of the KMS key must be @EXTERNAL@.
--
-- 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.
deleteImportedKeyMaterial_keyId :: Lens.Lens' DeleteImportedKeyMaterial Prelude.Text
deleteImportedKeyMaterial_keyId :: Lens' DeleteImportedKeyMaterial Text
deleteImportedKeyMaterial_keyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteImportedKeyMaterial' {Text
keyId :: Text
$sel:keyId:DeleteImportedKeyMaterial' :: DeleteImportedKeyMaterial -> Text
keyId} -> Text
keyId) (\s :: DeleteImportedKeyMaterial
s@DeleteImportedKeyMaterial' {} Text
a -> DeleteImportedKeyMaterial
s {$sel:keyId:DeleteImportedKeyMaterial' :: Text
keyId = Text
a} :: DeleteImportedKeyMaterial)

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

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

instance Prelude.NFData DeleteImportedKeyMaterial where
  rnf :: DeleteImportedKeyMaterial -> ()
rnf DeleteImportedKeyMaterial' {Text
keyId :: Text
$sel:keyId:DeleteImportedKeyMaterial' :: DeleteImportedKeyMaterial -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
keyId

instance Data.ToHeaders DeleteImportedKeyMaterial where
  toHeaders :: DeleteImportedKeyMaterial -> [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.DeleteImportedKeyMaterial" ::
                          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 DeleteImportedKeyMaterial where
  toJSON :: DeleteImportedKeyMaterial -> Value
toJSON DeleteImportedKeyMaterial' {Text
keyId :: Text
$sel:keyId:DeleteImportedKeyMaterial' :: DeleteImportedKeyMaterial -> 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)]
      )

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

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

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

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

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