{-# 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.SES.GetAccountSendingEnabled
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the email sending status of the Amazon SES account for the
-- current region.
--
-- You can execute this operation no more than once per second.
module Amazonka.SES.GetAccountSendingEnabled
  ( -- * Creating a Request
    GetAccountSendingEnabled (..),
    newGetAccountSendingEnabled,

    -- * Destructuring the Response
    GetAccountSendingEnabledResponse (..),
    newGetAccountSendingEnabledResponse,

    -- * Response Lenses
    getAccountSendingEnabledResponse_enabled,
    getAccountSendingEnabledResponse_httpStatus,
  )
where

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

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

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

instance Core.AWSRequest GetAccountSendingEnabled where
  type
    AWSResponse GetAccountSendingEnabled =
      GetAccountSendingEnabledResponse
  request :: (Service -> Service)
-> GetAccountSendingEnabled -> Request GetAccountSendingEnabled
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 GetAccountSendingEnabled
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetAccountSendingEnabled)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"GetAccountSendingEnabledResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Bool -> Int -> GetAccountSendingEnabledResponse
GetAccountSendingEnabledResponse'
            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
"Enabled")
            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 GetAccountSendingEnabled where
  hashWithSalt :: Int -> GetAccountSendingEnabled -> Int
hashWithSalt Int
_salt GetAccountSendingEnabled
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

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

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

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

instance Data.ToQuery GetAccountSendingEnabled where
  toQuery :: GetAccountSendingEnabled -> QueryString
toQuery =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ ByteString
"Action"
              forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"GetAccountSendingEnabled" :: Prelude.ByteString),
            ByteString
"Version"
              forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-12-01" :: Prelude.ByteString)
          ]
      )

-- | Represents a request to return the email sending status for your Amazon
-- SES account in the current AWS Region.
--
-- /See:/ 'newGetAccountSendingEnabledResponse' smart constructor.
data GetAccountSendingEnabledResponse = GetAccountSendingEnabledResponse'
  { -- | Describes whether email sending is enabled or disabled for your Amazon
    -- SES account in the current AWS Region.
    GetAccountSendingEnabledResponse -> Maybe Bool
enabled :: Prelude.Maybe Prelude.Bool,
    -- | The response's http status code.
    GetAccountSendingEnabledResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetAccountSendingEnabledResponse
-> GetAccountSendingEnabledResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAccountSendingEnabledResponse
-> GetAccountSendingEnabledResponse -> Bool
$c/= :: GetAccountSendingEnabledResponse
-> GetAccountSendingEnabledResponse -> Bool
== :: GetAccountSendingEnabledResponse
-> GetAccountSendingEnabledResponse -> Bool
$c== :: GetAccountSendingEnabledResponse
-> GetAccountSendingEnabledResponse -> Bool
Prelude.Eq, ReadPrec [GetAccountSendingEnabledResponse]
ReadPrec GetAccountSendingEnabledResponse
Int -> ReadS GetAccountSendingEnabledResponse
ReadS [GetAccountSendingEnabledResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetAccountSendingEnabledResponse]
$creadListPrec :: ReadPrec [GetAccountSendingEnabledResponse]
readPrec :: ReadPrec GetAccountSendingEnabledResponse
$creadPrec :: ReadPrec GetAccountSendingEnabledResponse
readList :: ReadS [GetAccountSendingEnabledResponse]
$creadList :: ReadS [GetAccountSendingEnabledResponse]
readsPrec :: Int -> ReadS GetAccountSendingEnabledResponse
$creadsPrec :: Int -> ReadS GetAccountSendingEnabledResponse
Prelude.Read, Int -> GetAccountSendingEnabledResponse -> ShowS
[GetAccountSendingEnabledResponse] -> ShowS
GetAccountSendingEnabledResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAccountSendingEnabledResponse] -> ShowS
$cshowList :: [GetAccountSendingEnabledResponse] -> ShowS
show :: GetAccountSendingEnabledResponse -> String
$cshow :: GetAccountSendingEnabledResponse -> String
showsPrec :: Int -> GetAccountSendingEnabledResponse -> ShowS
$cshowsPrec :: Int -> GetAccountSendingEnabledResponse -> ShowS
Prelude.Show, forall x.
Rep GetAccountSendingEnabledResponse x
-> GetAccountSendingEnabledResponse
forall x.
GetAccountSendingEnabledResponse
-> Rep GetAccountSendingEnabledResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetAccountSendingEnabledResponse x
-> GetAccountSendingEnabledResponse
$cfrom :: forall x.
GetAccountSendingEnabledResponse
-> Rep GetAccountSendingEnabledResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetAccountSendingEnabledResponse' 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:
--
-- 'enabled', 'getAccountSendingEnabledResponse_enabled' - Describes whether email sending is enabled or disabled for your Amazon
-- SES account in the current AWS Region.
--
-- 'httpStatus', 'getAccountSendingEnabledResponse_httpStatus' - The response's http status code.
newGetAccountSendingEnabledResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetAccountSendingEnabledResponse
newGetAccountSendingEnabledResponse :: Int -> GetAccountSendingEnabledResponse
newGetAccountSendingEnabledResponse Int
pHttpStatus_ =
  GetAccountSendingEnabledResponse'
    { $sel:enabled:GetAccountSendingEnabledResponse' :: Maybe Bool
enabled =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetAccountSendingEnabledResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Describes whether email sending is enabled or disabled for your Amazon
-- SES account in the current AWS Region.
getAccountSendingEnabledResponse_enabled :: Lens.Lens' GetAccountSendingEnabledResponse (Prelude.Maybe Prelude.Bool)
getAccountSendingEnabledResponse_enabled :: Lens' GetAccountSendingEnabledResponse (Maybe Bool)
getAccountSendingEnabledResponse_enabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAccountSendingEnabledResponse' {Maybe Bool
enabled :: Maybe Bool
$sel:enabled:GetAccountSendingEnabledResponse' :: GetAccountSendingEnabledResponse -> Maybe Bool
enabled} -> Maybe Bool
enabled) (\s :: GetAccountSendingEnabledResponse
s@GetAccountSendingEnabledResponse' {} Maybe Bool
a -> GetAccountSendingEnabledResponse
s {$sel:enabled:GetAccountSendingEnabledResponse' :: Maybe Bool
enabled = Maybe Bool
a} :: GetAccountSendingEnabledResponse)

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

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