{-# 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.ResetEbsDefaultKmsKeyId
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Resets the default KMS key for EBS encryption for your account in this
-- Region to the Amazon Web Services managed KMS key for EBS.
--
-- After resetting the default KMS key to the Amazon Web Services managed
-- KMS key, you can continue to encrypt by a customer managed KMS key by
-- specifying it when you create the volume. 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.ResetEbsDefaultKmsKeyId
  ( -- * Creating a Request
    ResetEbsDefaultKmsKeyId (..),
    newResetEbsDefaultKmsKeyId,

    -- * Request Lenses
    resetEbsDefaultKmsKeyId_dryRun,

    -- * Destructuring the Response
    ResetEbsDefaultKmsKeyIdResponse (..),
    newResetEbsDefaultKmsKeyIdResponse,

    -- * Response Lenses
    resetEbsDefaultKmsKeyIdResponse_kmsKeyId,
    resetEbsDefaultKmsKeyIdResponse_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:/ 'newResetEbsDefaultKmsKeyId' smart constructor.
data ResetEbsDefaultKmsKeyId = ResetEbsDefaultKmsKeyId'
  { -- | 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@.
    ResetEbsDefaultKmsKeyId -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool
  }
  deriving (ResetEbsDefaultKmsKeyId -> ResetEbsDefaultKmsKeyId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResetEbsDefaultKmsKeyId -> ResetEbsDefaultKmsKeyId -> Bool
$c/= :: ResetEbsDefaultKmsKeyId -> ResetEbsDefaultKmsKeyId -> Bool
== :: ResetEbsDefaultKmsKeyId -> ResetEbsDefaultKmsKeyId -> Bool
$c== :: ResetEbsDefaultKmsKeyId -> ResetEbsDefaultKmsKeyId -> Bool
Prelude.Eq, ReadPrec [ResetEbsDefaultKmsKeyId]
ReadPrec ResetEbsDefaultKmsKeyId
Int -> ReadS ResetEbsDefaultKmsKeyId
ReadS [ResetEbsDefaultKmsKeyId]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ResetEbsDefaultKmsKeyId]
$creadListPrec :: ReadPrec [ResetEbsDefaultKmsKeyId]
readPrec :: ReadPrec ResetEbsDefaultKmsKeyId
$creadPrec :: ReadPrec ResetEbsDefaultKmsKeyId
readList :: ReadS [ResetEbsDefaultKmsKeyId]
$creadList :: ReadS [ResetEbsDefaultKmsKeyId]
readsPrec :: Int -> ReadS ResetEbsDefaultKmsKeyId
$creadsPrec :: Int -> ReadS ResetEbsDefaultKmsKeyId
Prelude.Read, Int -> ResetEbsDefaultKmsKeyId -> ShowS
[ResetEbsDefaultKmsKeyId] -> ShowS
ResetEbsDefaultKmsKeyId -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResetEbsDefaultKmsKeyId] -> ShowS
$cshowList :: [ResetEbsDefaultKmsKeyId] -> ShowS
show :: ResetEbsDefaultKmsKeyId -> String
$cshow :: ResetEbsDefaultKmsKeyId -> String
showsPrec :: Int -> ResetEbsDefaultKmsKeyId -> ShowS
$cshowsPrec :: Int -> ResetEbsDefaultKmsKeyId -> ShowS
Prelude.Show, forall x. Rep ResetEbsDefaultKmsKeyId x -> ResetEbsDefaultKmsKeyId
forall x. ResetEbsDefaultKmsKeyId -> Rep ResetEbsDefaultKmsKeyId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResetEbsDefaultKmsKeyId x -> ResetEbsDefaultKmsKeyId
$cfrom :: forall x. ResetEbsDefaultKmsKeyId -> Rep ResetEbsDefaultKmsKeyId x
Prelude.Generic)

-- |
-- Create a value of 'ResetEbsDefaultKmsKeyId' 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', 'resetEbsDefaultKmsKeyId_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@.
newResetEbsDefaultKmsKeyId ::
  ResetEbsDefaultKmsKeyId
newResetEbsDefaultKmsKeyId :: ResetEbsDefaultKmsKeyId
newResetEbsDefaultKmsKeyId =
  ResetEbsDefaultKmsKeyId' {$sel:dryRun:ResetEbsDefaultKmsKeyId' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing}

-- | 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@.
resetEbsDefaultKmsKeyId_dryRun :: Lens.Lens' ResetEbsDefaultKmsKeyId (Prelude.Maybe Prelude.Bool)
resetEbsDefaultKmsKeyId_dryRun :: Lens' ResetEbsDefaultKmsKeyId (Maybe Bool)
resetEbsDefaultKmsKeyId_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResetEbsDefaultKmsKeyId' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:ResetEbsDefaultKmsKeyId' :: ResetEbsDefaultKmsKeyId -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: ResetEbsDefaultKmsKeyId
s@ResetEbsDefaultKmsKeyId' {} Maybe Bool
a -> ResetEbsDefaultKmsKeyId
s {$sel:dryRun:ResetEbsDefaultKmsKeyId' :: Maybe Bool
dryRun = Maybe Bool
a} :: ResetEbsDefaultKmsKeyId)

instance Core.AWSRequest ResetEbsDefaultKmsKeyId where
  type
    AWSResponse ResetEbsDefaultKmsKeyId =
      ResetEbsDefaultKmsKeyIdResponse
  request :: (Service -> Service)
-> ResetEbsDefaultKmsKeyId -> Request ResetEbsDefaultKmsKeyId
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 ResetEbsDefaultKmsKeyId
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ResetEbsDefaultKmsKeyId)))
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 -> ResetEbsDefaultKmsKeyIdResponse
ResetEbsDefaultKmsKeyIdResponse'
            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 ResetEbsDefaultKmsKeyId where
  hashWithSalt :: Int -> ResetEbsDefaultKmsKeyId -> Int
hashWithSalt Int
_salt ResetEbsDefaultKmsKeyId' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:ResetEbsDefaultKmsKeyId' :: ResetEbsDefaultKmsKeyId -> Maybe Bool
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun

instance Prelude.NFData ResetEbsDefaultKmsKeyId where
  rnf :: ResetEbsDefaultKmsKeyId -> ()
rnf ResetEbsDefaultKmsKeyId' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:ResetEbsDefaultKmsKeyId' :: ResetEbsDefaultKmsKeyId -> Maybe Bool
..} = forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun

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

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

instance Data.ToQuery ResetEbsDefaultKmsKeyId where
  toQuery :: ResetEbsDefaultKmsKeyId -> QueryString
toQuery ResetEbsDefaultKmsKeyId' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:ResetEbsDefaultKmsKeyId' :: ResetEbsDefaultKmsKeyId -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"ResetEbsDefaultKmsKeyId" :: 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
      ]

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

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

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

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

instance
  Prelude.NFData
    ResetEbsDefaultKmsKeyIdResponse
  where
  rnf :: ResetEbsDefaultKmsKeyIdResponse -> ()
rnf ResetEbsDefaultKmsKeyIdResponse' {Int
Maybe Text
httpStatus :: Int
kmsKeyId :: Maybe Text
$sel:httpStatus:ResetEbsDefaultKmsKeyIdResponse' :: ResetEbsDefaultKmsKeyIdResponse -> Int
$sel:kmsKeyId:ResetEbsDefaultKmsKeyIdResponse' :: ResetEbsDefaultKmsKeyIdResponse -> 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