{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.SESV2.Types.DeliverabilityTestReport
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.SESV2.Types.DeliverabilityTestReport 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 Amazonka.SESV2.Types.DeliverabilityTestStatus

-- | An object that contains metadata related to a predictive inbox placement
-- test.
--
-- /See:/ 'newDeliverabilityTestReport' smart constructor.
data DeliverabilityTestReport = DeliverabilityTestReport'
  { -- | The date and time when the predictive inbox placement test was created.
    DeliverabilityTestReport -> Maybe POSIX
createDate :: Prelude.Maybe Data.POSIX,
    -- | The status of the predictive inbox placement test. If the status is
    -- @IN_PROGRESS@, then the predictive inbox placement test is currently
    -- running. Predictive inbox placement tests are usually complete within 24
    -- hours of creating the test. If the status is @COMPLETE@, then the test
    -- is finished, and you can use the @GetDeliverabilityTestReport@ to view
    -- the results of the test.
    DeliverabilityTestReport -> Maybe DeliverabilityTestStatus
deliverabilityTestStatus :: Prelude.Maybe DeliverabilityTestStatus,
    -- | The sender address that you specified for the predictive inbox placement
    -- test.
    DeliverabilityTestReport -> Maybe Text
fromEmailAddress :: Prelude.Maybe Prelude.Text,
    -- | A unique string that identifies the predictive inbox placement test.
    DeliverabilityTestReport -> Maybe Text
reportId :: Prelude.Maybe Prelude.Text,
    -- | A name that helps you identify a predictive inbox placement test report.
    DeliverabilityTestReport -> Maybe Text
reportName :: Prelude.Maybe Prelude.Text,
    -- | The subject line for an email that you submitted in a predictive inbox
    -- placement test.
    DeliverabilityTestReport -> Maybe Text
subject :: Prelude.Maybe Prelude.Text
  }
  deriving (DeliverabilityTestReport -> DeliverabilityTestReport -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeliverabilityTestReport -> DeliverabilityTestReport -> Bool
$c/= :: DeliverabilityTestReport -> DeliverabilityTestReport -> Bool
== :: DeliverabilityTestReport -> DeliverabilityTestReport -> Bool
$c== :: DeliverabilityTestReport -> DeliverabilityTestReport -> Bool
Prelude.Eq, ReadPrec [DeliverabilityTestReport]
ReadPrec DeliverabilityTestReport
Int -> ReadS DeliverabilityTestReport
ReadS [DeliverabilityTestReport]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeliverabilityTestReport]
$creadListPrec :: ReadPrec [DeliverabilityTestReport]
readPrec :: ReadPrec DeliverabilityTestReport
$creadPrec :: ReadPrec DeliverabilityTestReport
readList :: ReadS [DeliverabilityTestReport]
$creadList :: ReadS [DeliverabilityTestReport]
readsPrec :: Int -> ReadS DeliverabilityTestReport
$creadsPrec :: Int -> ReadS DeliverabilityTestReport
Prelude.Read, Int -> DeliverabilityTestReport -> ShowS
[DeliverabilityTestReport] -> ShowS
DeliverabilityTestReport -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeliverabilityTestReport] -> ShowS
$cshowList :: [DeliverabilityTestReport] -> ShowS
show :: DeliverabilityTestReport -> String
$cshow :: DeliverabilityTestReport -> String
showsPrec :: Int -> DeliverabilityTestReport -> ShowS
$cshowsPrec :: Int -> DeliverabilityTestReport -> ShowS
Prelude.Show, forall x.
Rep DeliverabilityTestReport x -> DeliverabilityTestReport
forall x.
DeliverabilityTestReport -> Rep DeliverabilityTestReport x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeliverabilityTestReport x -> DeliverabilityTestReport
$cfrom :: forall x.
DeliverabilityTestReport -> Rep DeliverabilityTestReport x
Prelude.Generic)

-- |
-- Create a value of 'DeliverabilityTestReport' 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:
--
-- 'createDate', 'deliverabilityTestReport_createDate' - The date and time when the predictive inbox placement test was created.
--
-- 'deliverabilityTestStatus', 'deliverabilityTestReport_deliverabilityTestStatus' - The status of the predictive inbox placement test. If the status is
-- @IN_PROGRESS@, then the predictive inbox placement test is currently
-- running. Predictive inbox placement tests are usually complete within 24
-- hours of creating the test. If the status is @COMPLETE@, then the test
-- is finished, and you can use the @GetDeliverabilityTestReport@ to view
-- the results of the test.
--
-- 'fromEmailAddress', 'deliverabilityTestReport_fromEmailAddress' - The sender address that you specified for the predictive inbox placement
-- test.
--
-- 'reportId', 'deliverabilityTestReport_reportId' - A unique string that identifies the predictive inbox placement test.
--
-- 'reportName', 'deliverabilityTestReport_reportName' - A name that helps you identify a predictive inbox placement test report.
--
-- 'subject', 'deliverabilityTestReport_subject' - The subject line for an email that you submitted in a predictive inbox
-- placement test.
newDeliverabilityTestReport ::
  DeliverabilityTestReport
newDeliverabilityTestReport :: DeliverabilityTestReport
newDeliverabilityTestReport =
  DeliverabilityTestReport'
    { $sel:createDate:DeliverabilityTestReport' :: Maybe POSIX
createDate =
        forall a. Maybe a
Prelude.Nothing,
      $sel:deliverabilityTestStatus:DeliverabilityTestReport' :: Maybe DeliverabilityTestStatus
deliverabilityTestStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:fromEmailAddress:DeliverabilityTestReport' :: Maybe Text
fromEmailAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:reportId:DeliverabilityTestReport' :: Maybe Text
reportId = forall a. Maybe a
Prelude.Nothing,
      $sel:reportName:DeliverabilityTestReport' :: Maybe Text
reportName = forall a. Maybe a
Prelude.Nothing,
      $sel:subject:DeliverabilityTestReport' :: Maybe Text
subject = forall a. Maybe a
Prelude.Nothing
    }

-- | The date and time when the predictive inbox placement test was created.
deliverabilityTestReport_createDate :: Lens.Lens' DeliverabilityTestReport (Prelude.Maybe Prelude.UTCTime)
deliverabilityTestReport_createDate :: Lens' DeliverabilityTestReport (Maybe UTCTime)
deliverabilityTestReport_createDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliverabilityTestReport' {Maybe POSIX
createDate :: Maybe POSIX
$sel:createDate:DeliverabilityTestReport' :: DeliverabilityTestReport -> Maybe POSIX
createDate} -> Maybe POSIX
createDate) (\s :: DeliverabilityTestReport
s@DeliverabilityTestReport' {} Maybe POSIX
a -> DeliverabilityTestReport
s {$sel:createDate:DeliverabilityTestReport' :: Maybe POSIX
createDate = Maybe POSIX
a} :: DeliverabilityTestReport) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The status of the predictive inbox placement test. If the status is
-- @IN_PROGRESS@, then the predictive inbox placement test is currently
-- running. Predictive inbox placement tests are usually complete within 24
-- hours of creating the test. If the status is @COMPLETE@, then the test
-- is finished, and you can use the @GetDeliverabilityTestReport@ to view
-- the results of the test.
deliverabilityTestReport_deliverabilityTestStatus :: Lens.Lens' DeliverabilityTestReport (Prelude.Maybe DeliverabilityTestStatus)
deliverabilityTestReport_deliverabilityTestStatus :: Lens' DeliverabilityTestReport (Maybe DeliverabilityTestStatus)
deliverabilityTestReport_deliverabilityTestStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliverabilityTestReport' {Maybe DeliverabilityTestStatus
deliverabilityTestStatus :: Maybe DeliverabilityTestStatus
$sel:deliverabilityTestStatus:DeliverabilityTestReport' :: DeliverabilityTestReport -> Maybe DeliverabilityTestStatus
deliverabilityTestStatus} -> Maybe DeliverabilityTestStatus
deliverabilityTestStatus) (\s :: DeliverabilityTestReport
s@DeliverabilityTestReport' {} Maybe DeliverabilityTestStatus
a -> DeliverabilityTestReport
s {$sel:deliverabilityTestStatus:DeliverabilityTestReport' :: Maybe DeliverabilityTestStatus
deliverabilityTestStatus = Maybe DeliverabilityTestStatus
a} :: DeliverabilityTestReport)

-- | The sender address that you specified for the predictive inbox placement
-- test.
deliverabilityTestReport_fromEmailAddress :: Lens.Lens' DeliverabilityTestReport (Prelude.Maybe Prelude.Text)
deliverabilityTestReport_fromEmailAddress :: Lens' DeliverabilityTestReport (Maybe Text)
deliverabilityTestReport_fromEmailAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliverabilityTestReport' {Maybe Text
fromEmailAddress :: Maybe Text
$sel:fromEmailAddress:DeliverabilityTestReport' :: DeliverabilityTestReport -> Maybe Text
fromEmailAddress} -> Maybe Text
fromEmailAddress) (\s :: DeliverabilityTestReport
s@DeliverabilityTestReport' {} Maybe Text
a -> DeliverabilityTestReport
s {$sel:fromEmailAddress:DeliverabilityTestReport' :: Maybe Text
fromEmailAddress = Maybe Text
a} :: DeliverabilityTestReport)

-- | A unique string that identifies the predictive inbox placement test.
deliverabilityTestReport_reportId :: Lens.Lens' DeliverabilityTestReport (Prelude.Maybe Prelude.Text)
deliverabilityTestReport_reportId :: Lens' DeliverabilityTestReport (Maybe Text)
deliverabilityTestReport_reportId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliverabilityTestReport' {Maybe Text
reportId :: Maybe Text
$sel:reportId:DeliverabilityTestReport' :: DeliverabilityTestReport -> Maybe Text
reportId} -> Maybe Text
reportId) (\s :: DeliverabilityTestReport
s@DeliverabilityTestReport' {} Maybe Text
a -> DeliverabilityTestReport
s {$sel:reportId:DeliverabilityTestReport' :: Maybe Text
reportId = Maybe Text
a} :: DeliverabilityTestReport)

-- | A name that helps you identify a predictive inbox placement test report.
deliverabilityTestReport_reportName :: Lens.Lens' DeliverabilityTestReport (Prelude.Maybe Prelude.Text)
deliverabilityTestReport_reportName :: Lens' DeliverabilityTestReport (Maybe Text)
deliverabilityTestReport_reportName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliverabilityTestReport' {Maybe Text
reportName :: Maybe Text
$sel:reportName:DeliverabilityTestReport' :: DeliverabilityTestReport -> Maybe Text
reportName} -> Maybe Text
reportName) (\s :: DeliverabilityTestReport
s@DeliverabilityTestReport' {} Maybe Text
a -> DeliverabilityTestReport
s {$sel:reportName:DeliverabilityTestReport' :: Maybe Text
reportName = Maybe Text
a} :: DeliverabilityTestReport)

-- | The subject line for an email that you submitted in a predictive inbox
-- placement test.
deliverabilityTestReport_subject :: Lens.Lens' DeliverabilityTestReport (Prelude.Maybe Prelude.Text)
deliverabilityTestReport_subject :: Lens' DeliverabilityTestReport (Maybe Text)
deliverabilityTestReport_subject = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeliverabilityTestReport' {Maybe Text
subject :: Maybe Text
$sel:subject:DeliverabilityTestReport' :: DeliverabilityTestReport -> Maybe Text
subject} -> Maybe Text
subject) (\s :: DeliverabilityTestReport
s@DeliverabilityTestReport' {} Maybe Text
a -> DeliverabilityTestReport
s {$sel:subject:DeliverabilityTestReport' :: Maybe Text
subject = Maybe Text
a} :: DeliverabilityTestReport)

instance Data.FromJSON DeliverabilityTestReport where
  parseJSON :: Value -> Parser DeliverabilityTestReport
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"DeliverabilityTestReport"
      ( \Object
x ->
          Maybe POSIX
-> Maybe DeliverabilityTestStatus
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> DeliverabilityTestReport
DeliverabilityTestReport'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"CreateDate")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"DeliverabilityTestStatus")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"FromEmailAddress")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ReportId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ReportName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Subject")
      )

instance Prelude.Hashable DeliverabilityTestReport where
  hashWithSalt :: Int -> DeliverabilityTestReport -> Int
hashWithSalt Int
_salt DeliverabilityTestReport' {Maybe Text
Maybe POSIX
Maybe DeliverabilityTestStatus
subject :: Maybe Text
reportName :: Maybe Text
reportId :: Maybe Text
fromEmailAddress :: Maybe Text
deliverabilityTestStatus :: Maybe DeliverabilityTestStatus
createDate :: Maybe POSIX
$sel:subject:DeliverabilityTestReport' :: DeliverabilityTestReport -> Maybe Text
$sel:reportName:DeliverabilityTestReport' :: DeliverabilityTestReport -> Maybe Text
$sel:reportId:DeliverabilityTestReport' :: DeliverabilityTestReport -> Maybe Text
$sel:fromEmailAddress:DeliverabilityTestReport' :: DeliverabilityTestReport -> Maybe Text
$sel:deliverabilityTestStatus:DeliverabilityTestReport' :: DeliverabilityTestReport -> Maybe DeliverabilityTestStatus
$sel:createDate:DeliverabilityTestReport' :: DeliverabilityTestReport -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createDate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DeliverabilityTestStatus
deliverabilityTestStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
fromEmailAddress
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
reportId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
reportName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
subject

instance Prelude.NFData DeliverabilityTestReport where
  rnf :: DeliverabilityTestReport -> ()
rnf DeliverabilityTestReport' {Maybe Text
Maybe POSIX
Maybe DeliverabilityTestStatus
subject :: Maybe Text
reportName :: Maybe Text
reportId :: Maybe Text
fromEmailAddress :: Maybe Text
deliverabilityTestStatus :: Maybe DeliverabilityTestStatus
createDate :: Maybe POSIX
$sel:subject:DeliverabilityTestReport' :: DeliverabilityTestReport -> Maybe Text
$sel:reportName:DeliverabilityTestReport' :: DeliverabilityTestReport -> Maybe Text
$sel:reportId:DeliverabilityTestReport' :: DeliverabilityTestReport -> Maybe Text
$sel:fromEmailAddress:DeliverabilityTestReport' :: DeliverabilityTestReport -> Maybe Text
$sel:deliverabilityTestStatus:DeliverabilityTestReport' :: DeliverabilityTestReport -> Maybe DeliverabilityTestStatus
$sel:createDate:DeliverabilityTestReport' :: DeliverabilityTestReport -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DeliverabilityTestStatus
deliverabilityTestStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
fromEmailAddress
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
reportId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
reportName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
subject