{-# 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.GetSendStatistics
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Provides sending statistics for the current AWS Region. The result is a
-- list of data points, representing the last two weeks of sending
-- activity. Each data point in the list contains statistics for a
-- 15-minute period of time.
--
-- You can execute this operation no more than once per second.
module Amazonka.SES.GetSendStatistics
  ( -- * Creating a Request
    GetSendStatistics (..),
    newGetSendStatistics,

    -- * Destructuring the Response
    GetSendStatisticsResponse (..),
    newGetSendStatisticsResponse,

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

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

instance Core.AWSRequest GetSendStatistics where
  type
    AWSResponse GetSendStatistics =
      GetSendStatisticsResponse
  request :: (Service -> Service)
-> GetSendStatistics -> Request GetSendStatistics
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 GetSendStatistics
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetSendStatistics)))
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
"GetSendStatisticsResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe [SendDataPoint] -> Int -> GetSendStatisticsResponse
GetSendStatisticsResponse'
            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
"SendDataPoints"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                        )
            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 GetSendStatistics where
  hashWithSalt :: Int -> GetSendStatistics -> Int
hashWithSalt Int
_salt GetSendStatistics
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

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

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

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

instance Data.ToQuery GetSendStatistics where
  toQuery :: GetSendStatistics -> 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
"GetSendStatistics" :: Prelude.ByteString),
            ByteString
"Version"
              forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-12-01" :: Prelude.ByteString)
          ]
      )

-- | Represents a list of data points. This list contains aggregated data
-- from the previous two weeks of your sending activity with Amazon SES.
--
-- /See:/ 'newGetSendStatisticsResponse' smart constructor.
data GetSendStatisticsResponse = GetSendStatisticsResponse'
  { -- | A list of data points, each of which represents 15 minutes of activity.
    GetSendStatisticsResponse -> Maybe [SendDataPoint]
sendDataPoints :: Prelude.Maybe [SendDataPoint],
    -- | The response's http status code.
    GetSendStatisticsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetSendStatisticsResponse -> GetSendStatisticsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSendStatisticsResponse -> GetSendStatisticsResponse -> Bool
$c/= :: GetSendStatisticsResponse -> GetSendStatisticsResponse -> Bool
== :: GetSendStatisticsResponse -> GetSendStatisticsResponse -> Bool
$c== :: GetSendStatisticsResponse -> GetSendStatisticsResponse -> Bool
Prelude.Eq, ReadPrec [GetSendStatisticsResponse]
ReadPrec GetSendStatisticsResponse
Int -> ReadS GetSendStatisticsResponse
ReadS [GetSendStatisticsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSendStatisticsResponse]
$creadListPrec :: ReadPrec [GetSendStatisticsResponse]
readPrec :: ReadPrec GetSendStatisticsResponse
$creadPrec :: ReadPrec GetSendStatisticsResponse
readList :: ReadS [GetSendStatisticsResponse]
$creadList :: ReadS [GetSendStatisticsResponse]
readsPrec :: Int -> ReadS GetSendStatisticsResponse
$creadsPrec :: Int -> ReadS GetSendStatisticsResponse
Prelude.Read, Int -> GetSendStatisticsResponse -> ShowS
[GetSendStatisticsResponse] -> ShowS
GetSendStatisticsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSendStatisticsResponse] -> ShowS
$cshowList :: [GetSendStatisticsResponse] -> ShowS
show :: GetSendStatisticsResponse -> String
$cshow :: GetSendStatisticsResponse -> String
showsPrec :: Int -> GetSendStatisticsResponse -> ShowS
$cshowsPrec :: Int -> GetSendStatisticsResponse -> ShowS
Prelude.Show, forall x.
Rep GetSendStatisticsResponse x -> GetSendStatisticsResponse
forall x.
GetSendStatisticsResponse -> Rep GetSendStatisticsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetSendStatisticsResponse x -> GetSendStatisticsResponse
$cfrom :: forall x.
GetSendStatisticsResponse -> Rep GetSendStatisticsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetSendStatisticsResponse' 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:
--
-- 'sendDataPoints', 'getSendStatisticsResponse_sendDataPoints' - A list of data points, each of which represents 15 minutes of activity.
--
-- 'httpStatus', 'getSendStatisticsResponse_httpStatus' - The response's http status code.
newGetSendStatisticsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetSendStatisticsResponse
newGetSendStatisticsResponse :: Int -> GetSendStatisticsResponse
newGetSendStatisticsResponse Int
pHttpStatus_ =
  GetSendStatisticsResponse'
    { $sel:sendDataPoints:GetSendStatisticsResponse' :: Maybe [SendDataPoint]
sendDataPoints =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetSendStatisticsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of data points, each of which represents 15 minutes of activity.
getSendStatisticsResponse_sendDataPoints :: Lens.Lens' GetSendStatisticsResponse (Prelude.Maybe [SendDataPoint])
getSendStatisticsResponse_sendDataPoints :: Lens' GetSendStatisticsResponse (Maybe [SendDataPoint])
getSendStatisticsResponse_sendDataPoints = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSendStatisticsResponse' {Maybe [SendDataPoint]
sendDataPoints :: Maybe [SendDataPoint]
$sel:sendDataPoints:GetSendStatisticsResponse' :: GetSendStatisticsResponse -> Maybe [SendDataPoint]
sendDataPoints} -> Maybe [SendDataPoint]
sendDataPoints) (\s :: GetSendStatisticsResponse
s@GetSendStatisticsResponse' {} Maybe [SendDataPoint]
a -> GetSendStatisticsResponse
s {$sel:sendDataPoints:GetSendStatisticsResponse' :: Maybe [SendDataPoint]
sendDataPoints = Maybe [SendDataPoint]
a} :: GetSendStatisticsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData GetSendStatisticsResponse where
  rnf :: GetSendStatisticsResponse -> ()
rnf GetSendStatisticsResponse' {Int
Maybe [SendDataPoint]
httpStatus :: Int
sendDataPoints :: Maybe [SendDataPoint]
$sel:httpStatus:GetSendStatisticsResponse' :: GetSendStatisticsResponse -> Int
$sel:sendDataPoints:GetSendStatisticsResponse' :: GetSendStatisticsResponse -> Maybe [SendDataPoint]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [SendDataPoint]
sendDataPoints
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus