{-# 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.GetEbsDefaultKmsKeyId
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes the default KMS key for EBS encryption by default for your
-- account in this Region. You can change the default KMS key for
-- encryption by default using ModifyEbsDefaultKmsKeyId or
-- ResetEbsDefaultKmsKeyId.
--
-- 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.GetEbsDefaultKmsKeyId
  ( -- * Creating a Request
    GetEbsDefaultKmsKeyId (..),
    newGetEbsDefaultKmsKeyId,

    -- * Request Lenses
    getEbsDefaultKmsKeyId_dryRun,

    -- * Destructuring the Response
    GetEbsDefaultKmsKeyIdResponse (..),
    newGetEbsDefaultKmsKeyIdResponse,

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

-- |
-- Create a value of 'GetEbsDefaultKmsKeyId' 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', 'getEbsDefaultKmsKeyId_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@.
newGetEbsDefaultKmsKeyId ::
  GetEbsDefaultKmsKeyId
newGetEbsDefaultKmsKeyId :: GetEbsDefaultKmsKeyId
newGetEbsDefaultKmsKeyId =
  GetEbsDefaultKmsKeyId' {$sel:dryRun:GetEbsDefaultKmsKeyId' :: 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@.
getEbsDefaultKmsKeyId_dryRun :: Lens.Lens' GetEbsDefaultKmsKeyId (Prelude.Maybe Prelude.Bool)
getEbsDefaultKmsKeyId_dryRun :: Lens' GetEbsDefaultKmsKeyId (Maybe Bool)
getEbsDefaultKmsKeyId_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEbsDefaultKmsKeyId' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:GetEbsDefaultKmsKeyId' :: GetEbsDefaultKmsKeyId -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: GetEbsDefaultKmsKeyId
s@GetEbsDefaultKmsKeyId' {} Maybe Bool
a -> GetEbsDefaultKmsKeyId
s {$sel:dryRun:GetEbsDefaultKmsKeyId' :: Maybe Bool
dryRun = Maybe Bool
a} :: GetEbsDefaultKmsKeyId)

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

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

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

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

instance Data.ToQuery GetEbsDefaultKmsKeyId where
  toQuery :: GetEbsDefaultKmsKeyId -> QueryString
toQuery GetEbsDefaultKmsKeyId' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:GetEbsDefaultKmsKeyId' :: GetEbsDefaultKmsKeyId -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"GetEbsDefaultKmsKeyId" :: 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:/ 'newGetEbsDefaultKmsKeyIdResponse' smart constructor.
data GetEbsDefaultKmsKeyIdResponse = GetEbsDefaultKmsKeyIdResponse'
  { -- | The Amazon Resource Name (ARN) of the default KMS key for encryption by
    -- default.
    GetEbsDefaultKmsKeyIdResponse -> Maybe Text
kmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetEbsDefaultKmsKeyIdResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetEbsDefaultKmsKeyIdResponse
-> GetEbsDefaultKmsKeyIdResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetEbsDefaultKmsKeyIdResponse
-> GetEbsDefaultKmsKeyIdResponse -> Bool
$c/= :: GetEbsDefaultKmsKeyIdResponse
-> GetEbsDefaultKmsKeyIdResponse -> Bool
== :: GetEbsDefaultKmsKeyIdResponse
-> GetEbsDefaultKmsKeyIdResponse -> Bool
$c== :: GetEbsDefaultKmsKeyIdResponse
-> GetEbsDefaultKmsKeyIdResponse -> Bool
Prelude.Eq, ReadPrec [GetEbsDefaultKmsKeyIdResponse]
ReadPrec GetEbsDefaultKmsKeyIdResponse
Int -> ReadS GetEbsDefaultKmsKeyIdResponse
ReadS [GetEbsDefaultKmsKeyIdResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetEbsDefaultKmsKeyIdResponse]
$creadListPrec :: ReadPrec [GetEbsDefaultKmsKeyIdResponse]
readPrec :: ReadPrec GetEbsDefaultKmsKeyIdResponse
$creadPrec :: ReadPrec GetEbsDefaultKmsKeyIdResponse
readList :: ReadS [GetEbsDefaultKmsKeyIdResponse]
$creadList :: ReadS [GetEbsDefaultKmsKeyIdResponse]
readsPrec :: Int -> ReadS GetEbsDefaultKmsKeyIdResponse
$creadsPrec :: Int -> ReadS GetEbsDefaultKmsKeyIdResponse
Prelude.Read, Int -> GetEbsDefaultKmsKeyIdResponse -> ShowS
[GetEbsDefaultKmsKeyIdResponse] -> ShowS
GetEbsDefaultKmsKeyIdResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetEbsDefaultKmsKeyIdResponse] -> ShowS
$cshowList :: [GetEbsDefaultKmsKeyIdResponse] -> ShowS
show :: GetEbsDefaultKmsKeyIdResponse -> String
$cshow :: GetEbsDefaultKmsKeyIdResponse -> String
showsPrec :: Int -> GetEbsDefaultKmsKeyIdResponse -> ShowS
$cshowsPrec :: Int -> GetEbsDefaultKmsKeyIdResponse -> ShowS
Prelude.Show, forall x.
Rep GetEbsDefaultKmsKeyIdResponse x
-> GetEbsDefaultKmsKeyIdResponse
forall x.
GetEbsDefaultKmsKeyIdResponse
-> Rep GetEbsDefaultKmsKeyIdResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetEbsDefaultKmsKeyIdResponse x
-> GetEbsDefaultKmsKeyIdResponse
$cfrom :: forall x.
GetEbsDefaultKmsKeyIdResponse
-> Rep GetEbsDefaultKmsKeyIdResponse x
Prelude.Generic)

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

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

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

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