{-# 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.EC2.ModifyEbsDefaultKmsKeyId
-- 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 the default KMS key for EBS encryption by default for your
-- account in this Region.
--
-- Amazon Web Services creates a unique Amazon Web Services managed KMS key
-- in each Region for use with encryption by default. If you change the
-- default KMS key to a symmetric customer managed KMS key, it is used
-- instead of the Amazon Web Services managed KMS key. To reset the default
-- KMS key to the Amazon Web Services managed KMS key for EBS, use
-- ResetEbsDefaultKmsKeyId. Amazon EBS does not support asymmetric KMS
-- keys.
--
-- If you delete or disable the customer managed KMS key that you specified
-- for use with encryption by default, your instances will fail to launch.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/EBSEncryption.html Amazon EBS encryption>
-- in the /Amazon Elastic Compute Cloud User Guide/.
module Amazonka.EC2.ModifyEbsDefaultKmsKeyId
  ( -- * Creating a Request
    ModifyEbsDefaultKmsKeyId (..),
    newModifyEbsDefaultKmsKeyId,

    -- * Request Lenses
    modifyEbsDefaultKmsKeyId_dryRun,
    modifyEbsDefaultKmsKeyId_kmsKeyId,

    -- * Destructuring the Response
    ModifyEbsDefaultKmsKeyIdResponse (..),
    newModifyEbsDefaultKmsKeyIdResponse,

    -- * Response Lenses
    modifyEbsDefaultKmsKeyIdResponse_kmsKeyId,
    modifyEbsDefaultKmsKeyIdResponse_httpStatus,
  )
where

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

-- | /See:/ 'newModifyEbsDefaultKmsKeyId' smart constructor.
data ModifyEbsDefaultKmsKeyId = ModifyEbsDefaultKmsKeyId'
  { -- | Checks whether you have the required permissions for the action, without
    -- actually making the request, and provides an error response. If you have
    -- the required permissions, the error response is @DryRunOperation@.
    -- Otherwise, it is @UnauthorizedOperation@.
    ModifyEbsDefaultKmsKeyId -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The identifier of the Key Management Service (KMS) KMS key to use for
    -- Amazon EBS encryption. If this parameter is not specified, your KMS key
    -- for Amazon EBS is used. If @KmsKeyId@ is specified, the encrypted state
    -- must be @true@.
    --
    -- You can specify the KMS key using any of the following:
    --
    -- -   Key ID. For example, 1234abcd-12ab-34cd-56ef-1234567890ab.
    --
    -- -   Key alias. For example, alias\/ExampleAlias.
    --
    -- -   Key ARN. For example,
    --     arn:aws:kms:us-east-1:012345678910:key\/1234abcd-12ab-34cd-56ef-1234567890ab.
    --
    -- -   Alias ARN. For example,
    --     arn:aws:kms:us-east-1:012345678910:alias\/ExampleAlias.
    --
    -- Amazon Web Services authenticates the KMS key asynchronously. Therefore,
    -- if you specify an ID, alias, or ARN that is not valid, the action can
    -- appear to complete, but eventually fails.
    --
    -- Amazon EBS does not support asymmetric KMS keys.
    ModifyEbsDefaultKmsKeyId -> Text
kmsKeyId :: Prelude.Text
  }
  deriving (ModifyEbsDefaultKmsKeyId -> ModifyEbsDefaultKmsKeyId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModifyEbsDefaultKmsKeyId -> ModifyEbsDefaultKmsKeyId -> Bool
$c/= :: ModifyEbsDefaultKmsKeyId -> ModifyEbsDefaultKmsKeyId -> Bool
== :: ModifyEbsDefaultKmsKeyId -> ModifyEbsDefaultKmsKeyId -> Bool
$c== :: ModifyEbsDefaultKmsKeyId -> ModifyEbsDefaultKmsKeyId -> Bool
Prelude.Eq, ReadPrec [ModifyEbsDefaultKmsKeyId]
ReadPrec ModifyEbsDefaultKmsKeyId
Int -> ReadS ModifyEbsDefaultKmsKeyId
ReadS [ModifyEbsDefaultKmsKeyId]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModifyEbsDefaultKmsKeyId]
$creadListPrec :: ReadPrec [ModifyEbsDefaultKmsKeyId]
readPrec :: ReadPrec ModifyEbsDefaultKmsKeyId
$creadPrec :: ReadPrec ModifyEbsDefaultKmsKeyId
readList :: ReadS [ModifyEbsDefaultKmsKeyId]
$creadList :: ReadS [ModifyEbsDefaultKmsKeyId]
readsPrec :: Int -> ReadS ModifyEbsDefaultKmsKeyId
$creadsPrec :: Int -> ReadS ModifyEbsDefaultKmsKeyId
Prelude.Read, Int -> ModifyEbsDefaultKmsKeyId -> ShowS
[ModifyEbsDefaultKmsKeyId] -> ShowS
ModifyEbsDefaultKmsKeyId -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModifyEbsDefaultKmsKeyId] -> ShowS
$cshowList :: [ModifyEbsDefaultKmsKeyId] -> ShowS
show :: ModifyEbsDefaultKmsKeyId -> String
$cshow :: ModifyEbsDefaultKmsKeyId -> String
showsPrec :: Int -> ModifyEbsDefaultKmsKeyId -> ShowS
$cshowsPrec :: Int -> ModifyEbsDefaultKmsKeyId -> ShowS
Prelude.Show, forall x.
Rep ModifyEbsDefaultKmsKeyId x -> ModifyEbsDefaultKmsKeyId
forall x.
ModifyEbsDefaultKmsKeyId -> Rep ModifyEbsDefaultKmsKeyId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ModifyEbsDefaultKmsKeyId x -> ModifyEbsDefaultKmsKeyId
$cfrom :: forall x.
ModifyEbsDefaultKmsKeyId -> Rep ModifyEbsDefaultKmsKeyId x
Prelude.Generic)

-- |
-- Create a value of 'ModifyEbsDefaultKmsKeyId' 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:
--
-- 'dryRun', 'modifyEbsDefaultKmsKeyId_dryRun' - Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
--
-- 'kmsKeyId', 'modifyEbsDefaultKmsKeyId_kmsKeyId' - The identifier of the Key Management Service (KMS) KMS key to use for
-- Amazon EBS encryption. If this parameter is not specified, your KMS key
-- for Amazon EBS is used. If @KmsKeyId@ is specified, the encrypted state
-- must be @true@.
--
-- You can specify the KMS key using any of the following:
--
-- -   Key ID. For example, 1234abcd-12ab-34cd-56ef-1234567890ab.
--
-- -   Key alias. For example, alias\/ExampleAlias.
--
-- -   Key ARN. For example,
--     arn:aws:kms:us-east-1:012345678910:key\/1234abcd-12ab-34cd-56ef-1234567890ab.
--
-- -   Alias ARN. For example,
--     arn:aws:kms:us-east-1:012345678910:alias\/ExampleAlias.
--
-- Amazon Web Services authenticates the KMS key asynchronously. Therefore,
-- if you specify an ID, alias, or ARN that is not valid, the action can
-- appear to complete, but eventually fails.
--
-- Amazon EBS does not support asymmetric KMS keys.
newModifyEbsDefaultKmsKeyId ::
  -- | 'kmsKeyId'
  Prelude.Text ->
  ModifyEbsDefaultKmsKeyId
newModifyEbsDefaultKmsKeyId :: Text -> ModifyEbsDefaultKmsKeyId
newModifyEbsDefaultKmsKeyId Text
pKmsKeyId_ =
  ModifyEbsDefaultKmsKeyId'
    { $sel:dryRun:ModifyEbsDefaultKmsKeyId' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:kmsKeyId:ModifyEbsDefaultKmsKeyId' :: Text
kmsKeyId = Text
pKmsKeyId_
    }

-- | Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
modifyEbsDefaultKmsKeyId_dryRun :: Lens.Lens' ModifyEbsDefaultKmsKeyId (Prelude.Maybe Prelude.Bool)
modifyEbsDefaultKmsKeyId_dryRun :: Lens' ModifyEbsDefaultKmsKeyId (Maybe Bool)
modifyEbsDefaultKmsKeyId_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyEbsDefaultKmsKeyId' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:ModifyEbsDefaultKmsKeyId' :: ModifyEbsDefaultKmsKeyId -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: ModifyEbsDefaultKmsKeyId
s@ModifyEbsDefaultKmsKeyId' {} Maybe Bool
a -> ModifyEbsDefaultKmsKeyId
s {$sel:dryRun:ModifyEbsDefaultKmsKeyId' :: Maybe Bool
dryRun = Maybe Bool
a} :: ModifyEbsDefaultKmsKeyId)

-- | The identifier of the Key Management Service (KMS) KMS key to use for
-- Amazon EBS encryption. If this parameter is not specified, your KMS key
-- for Amazon EBS is used. If @KmsKeyId@ is specified, the encrypted state
-- must be @true@.
--
-- You can specify the KMS key using any of the following:
--
-- -   Key ID. For example, 1234abcd-12ab-34cd-56ef-1234567890ab.
--
-- -   Key alias. For example, alias\/ExampleAlias.
--
-- -   Key ARN. For example,
--     arn:aws:kms:us-east-1:012345678910:key\/1234abcd-12ab-34cd-56ef-1234567890ab.
--
-- -   Alias ARN. For example,
--     arn:aws:kms:us-east-1:012345678910:alias\/ExampleAlias.
--
-- Amazon Web Services authenticates the KMS key asynchronously. Therefore,
-- if you specify an ID, alias, or ARN that is not valid, the action can
-- appear to complete, but eventually fails.
--
-- Amazon EBS does not support asymmetric KMS keys.
modifyEbsDefaultKmsKeyId_kmsKeyId :: Lens.Lens' ModifyEbsDefaultKmsKeyId Prelude.Text
modifyEbsDefaultKmsKeyId_kmsKeyId :: Lens' ModifyEbsDefaultKmsKeyId Text
modifyEbsDefaultKmsKeyId_kmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyEbsDefaultKmsKeyId' {Text
kmsKeyId :: Text
$sel:kmsKeyId:ModifyEbsDefaultKmsKeyId' :: ModifyEbsDefaultKmsKeyId -> Text
kmsKeyId} -> Text
kmsKeyId) (\s :: ModifyEbsDefaultKmsKeyId
s@ModifyEbsDefaultKmsKeyId' {} Text
a -> ModifyEbsDefaultKmsKeyId
s {$sel:kmsKeyId:ModifyEbsDefaultKmsKeyId' :: Text
kmsKeyId = Text
a} :: ModifyEbsDefaultKmsKeyId)

instance Core.AWSRequest ModifyEbsDefaultKmsKeyId where
  type
    AWSResponse ModifyEbsDefaultKmsKeyId =
      ModifyEbsDefaultKmsKeyIdResponse
  request :: (Service -> Service)
-> ModifyEbsDefaultKmsKeyId -> Request ModifyEbsDefaultKmsKeyId
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ModifyEbsDefaultKmsKeyId
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ModifyEbsDefaultKmsKeyId)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text -> Int -> ModifyEbsDefaultKmsKeyIdResponse
ModifyEbsDefaultKmsKeyIdResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"kmsKeyId")
            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 ModifyEbsDefaultKmsKeyId where
  hashWithSalt :: Int -> ModifyEbsDefaultKmsKeyId -> Int
hashWithSalt Int
_salt ModifyEbsDefaultKmsKeyId' {Maybe Bool
Text
kmsKeyId :: Text
dryRun :: Maybe Bool
$sel:kmsKeyId:ModifyEbsDefaultKmsKeyId' :: ModifyEbsDefaultKmsKeyId -> Text
$sel:dryRun:ModifyEbsDefaultKmsKeyId' :: ModifyEbsDefaultKmsKeyId -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
kmsKeyId

instance Prelude.NFData ModifyEbsDefaultKmsKeyId where
  rnf :: ModifyEbsDefaultKmsKeyId -> ()
rnf ModifyEbsDefaultKmsKeyId' {Maybe Bool
Text
kmsKeyId :: Text
dryRun :: Maybe Bool
$sel:kmsKeyId:ModifyEbsDefaultKmsKeyId' :: ModifyEbsDefaultKmsKeyId -> Text
$sel:dryRun:ModifyEbsDefaultKmsKeyId' :: ModifyEbsDefaultKmsKeyId -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
kmsKeyId

instance Data.ToHeaders ModifyEbsDefaultKmsKeyId where
  toHeaders :: ModifyEbsDefaultKmsKeyId -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery ModifyEbsDefaultKmsKeyId where
  toQuery :: ModifyEbsDefaultKmsKeyId -> QueryString
toQuery ModifyEbsDefaultKmsKeyId' {Maybe Bool
Text
kmsKeyId :: Text
dryRun :: Maybe Bool
$sel:kmsKeyId:ModifyEbsDefaultKmsKeyId' :: ModifyEbsDefaultKmsKeyId -> Text
$sel:dryRun:ModifyEbsDefaultKmsKeyId' :: ModifyEbsDefaultKmsKeyId -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"ModifyEbsDefaultKmsKeyId" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        ByteString
"KmsKeyId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
kmsKeyId
      ]

-- | /See:/ 'newModifyEbsDefaultKmsKeyIdResponse' smart constructor.
data ModifyEbsDefaultKmsKeyIdResponse = ModifyEbsDefaultKmsKeyIdResponse'
  { -- | The Amazon Resource Name (ARN) of the default KMS key for encryption by
    -- default.
    ModifyEbsDefaultKmsKeyIdResponse -> Maybe Text
kmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ModifyEbsDefaultKmsKeyIdResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ModifyEbsDefaultKmsKeyIdResponse
-> ModifyEbsDefaultKmsKeyIdResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModifyEbsDefaultKmsKeyIdResponse
-> ModifyEbsDefaultKmsKeyIdResponse -> Bool
$c/= :: ModifyEbsDefaultKmsKeyIdResponse
-> ModifyEbsDefaultKmsKeyIdResponse -> Bool
== :: ModifyEbsDefaultKmsKeyIdResponse
-> ModifyEbsDefaultKmsKeyIdResponse -> Bool
$c== :: ModifyEbsDefaultKmsKeyIdResponse
-> ModifyEbsDefaultKmsKeyIdResponse -> Bool
Prelude.Eq, ReadPrec [ModifyEbsDefaultKmsKeyIdResponse]
ReadPrec ModifyEbsDefaultKmsKeyIdResponse
Int -> ReadS ModifyEbsDefaultKmsKeyIdResponse
ReadS [ModifyEbsDefaultKmsKeyIdResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModifyEbsDefaultKmsKeyIdResponse]
$creadListPrec :: ReadPrec [ModifyEbsDefaultKmsKeyIdResponse]
readPrec :: ReadPrec ModifyEbsDefaultKmsKeyIdResponse
$creadPrec :: ReadPrec ModifyEbsDefaultKmsKeyIdResponse
readList :: ReadS [ModifyEbsDefaultKmsKeyIdResponse]
$creadList :: ReadS [ModifyEbsDefaultKmsKeyIdResponse]
readsPrec :: Int -> ReadS ModifyEbsDefaultKmsKeyIdResponse
$creadsPrec :: Int -> ReadS ModifyEbsDefaultKmsKeyIdResponse
Prelude.Read, Int -> ModifyEbsDefaultKmsKeyIdResponse -> ShowS
[ModifyEbsDefaultKmsKeyIdResponse] -> ShowS
ModifyEbsDefaultKmsKeyIdResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModifyEbsDefaultKmsKeyIdResponse] -> ShowS
$cshowList :: [ModifyEbsDefaultKmsKeyIdResponse] -> ShowS
show :: ModifyEbsDefaultKmsKeyIdResponse -> String
$cshow :: ModifyEbsDefaultKmsKeyIdResponse -> String
showsPrec :: Int -> ModifyEbsDefaultKmsKeyIdResponse -> ShowS
$cshowsPrec :: Int -> ModifyEbsDefaultKmsKeyIdResponse -> ShowS
Prelude.Show, forall x.
Rep ModifyEbsDefaultKmsKeyIdResponse x
-> ModifyEbsDefaultKmsKeyIdResponse
forall x.
ModifyEbsDefaultKmsKeyIdResponse
-> Rep ModifyEbsDefaultKmsKeyIdResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ModifyEbsDefaultKmsKeyIdResponse x
-> ModifyEbsDefaultKmsKeyIdResponse
$cfrom :: forall x.
ModifyEbsDefaultKmsKeyIdResponse
-> Rep ModifyEbsDefaultKmsKeyIdResponse x
Prelude.Generic)

-- |
-- Create a value of 'ModifyEbsDefaultKmsKeyIdResponse' 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:
--
-- 'kmsKeyId', 'modifyEbsDefaultKmsKeyIdResponse_kmsKeyId' - The Amazon Resource Name (ARN) of the default KMS key for encryption by
-- default.
--
-- 'httpStatus', 'modifyEbsDefaultKmsKeyIdResponse_httpStatus' - The response's http status code.
newModifyEbsDefaultKmsKeyIdResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ModifyEbsDefaultKmsKeyIdResponse
newModifyEbsDefaultKmsKeyIdResponse :: Int -> ModifyEbsDefaultKmsKeyIdResponse
newModifyEbsDefaultKmsKeyIdResponse Int
pHttpStatus_ =
  ModifyEbsDefaultKmsKeyIdResponse'
    { $sel:kmsKeyId:ModifyEbsDefaultKmsKeyIdResponse' :: Maybe Text
kmsKeyId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ModifyEbsDefaultKmsKeyIdResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the default KMS key for encryption by
-- default.
modifyEbsDefaultKmsKeyIdResponse_kmsKeyId :: Lens.Lens' ModifyEbsDefaultKmsKeyIdResponse (Prelude.Maybe Prelude.Text)
modifyEbsDefaultKmsKeyIdResponse_kmsKeyId :: Lens' ModifyEbsDefaultKmsKeyIdResponse (Maybe Text)
modifyEbsDefaultKmsKeyIdResponse_kmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyEbsDefaultKmsKeyIdResponse' {Maybe Text
kmsKeyId :: Maybe Text
$sel:kmsKeyId:ModifyEbsDefaultKmsKeyIdResponse' :: ModifyEbsDefaultKmsKeyIdResponse -> Maybe Text
kmsKeyId} -> Maybe Text
kmsKeyId) (\s :: ModifyEbsDefaultKmsKeyIdResponse
s@ModifyEbsDefaultKmsKeyIdResponse' {} Maybe Text
a -> ModifyEbsDefaultKmsKeyIdResponse
s {$sel:kmsKeyId:ModifyEbsDefaultKmsKeyIdResponse' :: Maybe Text
kmsKeyId = Maybe Text
a} :: ModifyEbsDefaultKmsKeyIdResponse)

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

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