{-# 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.Backup.Types.ReportPlan
-- 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.Backup.Types.ReportPlan where

import Amazonka.Backup.Types.ReportDeliveryChannel
import Amazonka.Backup.Types.ReportSetting
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

-- | Contains detailed information about a report plan.
--
-- /See:/ 'newReportPlan' smart constructor.
data ReportPlan = ReportPlan'
  { -- | The date and time that a report plan is created, in Unix format and
    -- Coordinated Universal Time (UTC). The value of @CreationTime@ is
    -- accurate to milliseconds. For example, the value 1516925490.087
    -- represents Friday, January 26, 2018 12:11:30.087 AM.
    ReportPlan -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | The deployment status of a report plan. The statuses are:
    --
    -- @CREATE_IN_PROGRESS | UPDATE_IN_PROGRESS | DELETE_IN_PROGRESS | COMPLETED@
    ReportPlan -> Maybe Text
deploymentStatus :: Prelude.Maybe Prelude.Text,
    -- | The date and time that a report job associated with this report plan
    -- last attempted to run, in Unix format and Coordinated Universal Time
    -- (UTC). The value of @LastAttemptedExecutionTime@ is accurate to
    -- milliseconds. For example, the value 1516925490.087 represents Friday,
    -- January 26, 2018 12:11:30.087 AM.
    ReportPlan -> Maybe POSIX
lastAttemptedExecutionTime :: Prelude.Maybe Data.POSIX,
    -- | The date and time that a report job associated with this report plan
    -- last successfully ran, in Unix format and Coordinated Universal Time
    -- (UTC). The value of @LastSuccessfulExecutionTime@ is accurate to
    -- milliseconds. For example, the value 1516925490.087 represents Friday,
    -- January 26, 2018 12:11:30.087 AM.
    ReportPlan -> Maybe POSIX
lastSuccessfulExecutionTime :: Prelude.Maybe Data.POSIX,
    -- | Contains information about where and how to deliver your reports,
    -- specifically your Amazon S3 bucket name, S3 key prefix, and the formats
    -- of your reports.
    ReportPlan -> Maybe ReportDeliveryChannel
reportDeliveryChannel :: Prelude.Maybe ReportDeliveryChannel,
    -- | An Amazon Resource Name (ARN) that uniquely identifies a resource. The
    -- format of the ARN depends on the resource type.
    ReportPlan -> Maybe Text
reportPlanArn :: Prelude.Maybe Prelude.Text,
    -- | An optional description of the report plan with a maximum 1,024
    -- characters.
    ReportPlan -> Maybe Text
reportPlanDescription :: Prelude.Maybe Prelude.Text,
    -- | The unique name of the report plan. This name is between 1 and 256
    -- characters starting with a letter, and consisting of letters (a-z, A-Z),
    -- numbers (0-9), and underscores (_).
    ReportPlan -> Maybe Text
reportPlanName :: Prelude.Maybe Prelude.Text,
    -- | Identifies the report template for the report. Reports are built using a
    -- report template. The report templates are:
    --
    -- @RESOURCE_COMPLIANCE_REPORT | CONTROL_COMPLIANCE_REPORT | BACKUP_JOB_REPORT | COPY_JOB_REPORT | RESTORE_JOB_REPORT@
    --
    -- If the report template is @RESOURCE_COMPLIANCE_REPORT@ or
    -- @CONTROL_COMPLIANCE_REPORT@, this API resource also describes the report
    -- coverage by Amazon Web Services Regions and frameworks.
    ReportPlan -> Maybe ReportSetting
reportSetting :: Prelude.Maybe ReportSetting
  }
  deriving (ReportPlan -> ReportPlan -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReportPlan -> ReportPlan -> Bool
$c/= :: ReportPlan -> ReportPlan -> Bool
== :: ReportPlan -> ReportPlan -> Bool
$c== :: ReportPlan -> ReportPlan -> Bool
Prelude.Eq, ReadPrec [ReportPlan]
ReadPrec ReportPlan
Int -> ReadS ReportPlan
ReadS [ReportPlan]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ReportPlan]
$creadListPrec :: ReadPrec [ReportPlan]
readPrec :: ReadPrec ReportPlan
$creadPrec :: ReadPrec ReportPlan
readList :: ReadS [ReportPlan]
$creadList :: ReadS [ReportPlan]
readsPrec :: Int -> ReadS ReportPlan
$creadsPrec :: Int -> ReadS ReportPlan
Prelude.Read, Int -> ReportPlan -> ShowS
[ReportPlan] -> ShowS
ReportPlan -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReportPlan] -> ShowS
$cshowList :: [ReportPlan] -> ShowS
show :: ReportPlan -> String
$cshow :: ReportPlan -> String
showsPrec :: Int -> ReportPlan -> ShowS
$cshowsPrec :: Int -> ReportPlan -> ShowS
Prelude.Show, forall x. Rep ReportPlan x -> ReportPlan
forall x. ReportPlan -> Rep ReportPlan x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReportPlan x -> ReportPlan
$cfrom :: forall x. ReportPlan -> Rep ReportPlan x
Prelude.Generic)

-- |
-- Create a value of 'ReportPlan' 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:
--
-- 'creationTime', 'reportPlan_creationTime' - The date and time that a report plan is created, in Unix format and
-- Coordinated Universal Time (UTC). The value of @CreationTime@ is
-- accurate to milliseconds. For example, the value 1516925490.087
-- represents Friday, January 26, 2018 12:11:30.087 AM.
--
-- 'deploymentStatus', 'reportPlan_deploymentStatus' - The deployment status of a report plan. The statuses are:
--
-- @CREATE_IN_PROGRESS | UPDATE_IN_PROGRESS | DELETE_IN_PROGRESS | COMPLETED@
--
-- 'lastAttemptedExecutionTime', 'reportPlan_lastAttemptedExecutionTime' - The date and time that a report job associated with this report plan
-- last attempted to run, in Unix format and Coordinated Universal Time
-- (UTC). The value of @LastAttemptedExecutionTime@ is accurate to
-- milliseconds. For example, the value 1516925490.087 represents Friday,
-- January 26, 2018 12:11:30.087 AM.
--
-- 'lastSuccessfulExecutionTime', 'reportPlan_lastSuccessfulExecutionTime' - The date and time that a report job associated with this report plan
-- last successfully ran, in Unix format and Coordinated Universal Time
-- (UTC). The value of @LastSuccessfulExecutionTime@ is accurate to
-- milliseconds. For example, the value 1516925490.087 represents Friday,
-- January 26, 2018 12:11:30.087 AM.
--
-- 'reportDeliveryChannel', 'reportPlan_reportDeliveryChannel' - Contains information about where and how to deliver your reports,
-- specifically your Amazon S3 bucket name, S3 key prefix, and the formats
-- of your reports.
--
-- 'reportPlanArn', 'reportPlan_reportPlanArn' - An Amazon Resource Name (ARN) that uniquely identifies a resource. The
-- format of the ARN depends on the resource type.
--
-- 'reportPlanDescription', 'reportPlan_reportPlanDescription' - An optional description of the report plan with a maximum 1,024
-- characters.
--
-- 'reportPlanName', 'reportPlan_reportPlanName' - The unique name of the report plan. This name is between 1 and 256
-- characters starting with a letter, and consisting of letters (a-z, A-Z),
-- numbers (0-9), and underscores (_).
--
-- 'reportSetting', 'reportPlan_reportSetting' - Identifies the report template for the report. Reports are built using a
-- report template. The report templates are:
--
-- @RESOURCE_COMPLIANCE_REPORT | CONTROL_COMPLIANCE_REPORT | BACKUP_JOB_REPORT | COPY_JOB_REPORT | RESTORE_JOB_REPORT@
--
-- If the report template is @RESOURCE_COMPLIANCE_REPORT@ or
-- @CONTROL_COMPLIANCE_REPORT@, this API resource also describes the report
-- coverage by Amazon Web Services Regions and frameworks.
newReportPlan ::
  ReportPlan
newReportPlan :: ReportPlan
newReportPlan =
  ReportPlan'
    { $sel:creationTime:ReportPlan' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:deploymentStatus:ReportPlan' :: Maybe Text
deploymentStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:lastAttemptedExecutionTime:ReportPlan' :: Maybe POSIX
lastAttemptedExecutionTime = forall a. Maybe a
Prelude.Nothing,
      $sel:lastSuccessfulExecutionTime:ReportPlan' :: Maybe POSIX
lastSuccessfulExecutionTime = forall a. Maybe a
Prelude.Nothing,
      $sel:reportDeliveryChannel:ReportPlan' :: Maybe ReportDeliveryChannel
reportDeliveryChannel = forall a. Maybe a
Prelude.Nothing,
      $sel:reportPlanArn:ReportPlan' :: Maybe Text
reportPlanArn = forall a. Maybe a
Prelude.Nothing,
      $sel:reportPlanDescription:ReportPlan' :: Maybe Text
reportPlanDescription = forall a. Maybe a
Prelude.Nothing,
      $sel:reportPlanName:ReportPlan' :: Maybe Text
reportPlanName = forall a. Maybe a
Prelude.Nothing,
      $sel:reportSetting:ReportPlan' :: Maybe ReportSetting
reportSetting = forall a. Maybe a
Prelude.Nothing
    }

-- | The date and time that a report plan is created, in Unix format and
-- Coordinated Universal Time (UTC). The value of @CreationTime@ is
-- accurate to milliseconds. For example, the value 1516925490.087
-- represents Friday, January 26, 2018 12:11:30.087 AM.
reportPlan_creationTime :: Lens.Lens' ReportPlan (Prelude.Maybe Prelude.UTCTime)
reportPlan_creationTime :: Lens' ReportPlan (Maybe UTCTime)
reportPlan_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReportPlan' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:ReportPlan' :: ReportPlan -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: ReportPlan
s@ReportPlan' {} Maybe POSIX
a -> ReportPlan
s {$sel:creationTime:ReportPlan' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: ReportPlan) 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 deployment status of a report plan. The statuses are:
--
-- @CREATE_IN_PROGRESS | UPDATE_IN_PROGRESS | DELETE_IN_PROGRESS | COMPLETED@
reportPlan_deploymentStatus :: Lens.Lens' ReportPlan (Prelude.Maybe Prelude.Text)
reportPlan_deploymentStatus :: Lens' ReportPlan (Maybe Text)
reportPlan_deploymentStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReportPlan' {Maybe Text
deploymentStatus :: Maybe Text
$sel:deploymentStatus:ReportPlan' :: ReportPlan -> Maybe Text
deploymentStatus} -> Maybe Text
deploymentStatus) (\s :: ReportPlan
s@ReportPlan' {} Maybe Text
a -> ReportPlan
s {$sel:deploymentStatus:ReportPlan' :: Maybe Text
deploymentStatus = Maybe Text
a} :: ReportPlan)

-- | The date and time that a report job associated with this report plan
-- last attempted to run, in Unix format and Coordinated Universal Time
-- (UTC). The value of @LastAttemptedExecutionTime@ is accurate to
-- milliseconds. For example, the value 1516925490.087 represents Friday,
-- January 26, 2018 12:11:30.087 AM.
reportPlan_lastAttemptedExecutionTime :: Lens.Lens' ReportPlan (Prelude.Maybe Prelude.UTCTime)
reportPlan_lastAttemptedExecutionTime :: Lens' ReportPlan (Maybe UTCTime)
reportPlan_lastAttemptedExecutionTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReportPlan' {Maybe POSIX
lastAttemptedExecutionTime :: Maybe POSIX
$sel:lastAttemptedExecutionTime:ReportPlan' :: ReportPlan -> Maybe POSIX
lastAttemptedExecutionTime} -> Maybe POSIX
lastAttemptedExecutionTime) (\s :: ReportPlan
s@ReportPlan' {} Maybe POSIX
a -> ReportPlan
s {$sel:lastAttemptedExecutionTime:ReportPlan' :: Maybe POSIX
lastAttemptedExecutionTime = Maybe POSIX
a} :: ReportPlan) 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 date and time that a report job associated with this report plan
-- last successfully ran, in Unix format and Coordinated Universal Time
-- (UTC). The value of @LastSuccessfulExecutionTime@ is accurate to
-- milliseconds. For example, the value 1516925490.087 represents Friday,
-- January 26, 2018 12:11:30.087 AM.
reportPlan_lastSuccessfulExecutionTime :: Lens.Lens' ReportPlan (Prelude.Maybe Prelude.UTCTime)
reportPlan_lastSuccessfulExecutionTime :: Lens' ReportPlan (Maybe UTCTime)
reportPlan_lastSuccessfulExecutionTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReportPlan' {Maybe POSIX
lastSuccessfulExecutionTime :: Maybe POSIX
$sel:lastSuccessfulExecutionTime:ReportPlan' :: ReportPlan -> Maybe POSIX
lastSuccessfulExecutionTime} -> Maybe POSIX
lastSuccessfulExecutionTime) (\s :: ReportPlan
s@ReportPlan' {} Maybe POSIX
a -> ReportPlan
s {$sel:lastSuccessfulExecutionTime:ReportPlan' :: Maybe POSIX
lastSuccessfulExecutionTime = Maybe POSIX
a} :: ReportPlan) 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

-- | Contains information about where and how to deliver your reports,
-- specifically your Amazon S3 bucket name, S3 key prefix, and the formats
-- of your reports.
reportPlan_reportDeliveryChannel :: Lens.Lens' ReportPlan (Prelude.Maybe ReportDeliveryChannel)
reportPlan_reportDeliveryChannel :: Lens' ReportPlan (Maybe ReportDeliveryChannel)
reportPlan_reportDeliveryChannel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReportPlan' {Maybe ReportDeliveryChannel
reportDeliveryChannel :: Maybe ReportDeliveryChannel
$sel:reportDeliveryChannel:ReportPlan' :: ReportPlan -> Maybe ReportDeliveryChannel
reportDeliveryChannel} -> Maybe ReportDeliveryChannel
reportDeliveryChannel) (\s :: ReportPlan
s@ReportPlan' {} Maybe ReportDeliveryChannel
a -> ReportPlan
s {$sel:reportDeliveryChannel:ReportPlan' :: Maybe ReportDeliveryChannel
reportDeliveryChannel = Maybe ReportDeliveryChannel
a} :: ReportPlan)

-- | An Amazon Resource Name (ARN) that uniquely identifies a resource. The
-- format of the ARN depends on the resource type.
reportPlan_reportPlanArn :: Lens.Lens' ReportPlan (Prelude.Maybe Prelude.Text)
reportPlan_reportPlanArn :: Lens' ReportPlan (Maybe Text)
reportPlan_reportPlanArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReportPlan' {Maybe Text
reportPlanArn :: Maybe Text
$sel:reportPlanArn:ReportPlan' :: ReportPlan -> Maybe Text
reportPlanArn} -> Maybe Text
reportPlanArn) (\s :: ReportPlan
s@ReportPlan' {} Maybe Text
a -> ReportPlan
s {$sel:reportPlanArn:ReportPlan' :: Maybe Text
reportPlanArn = Maybe Text
a} :: ReportPlan)

-- | An optional description of the report plan with a maximum 1,024
-- characters.
reportPlan_reportPlanDescription :: Lens.Lens' ReportPlan (Prelude.Maybe Prelude.Text)
reportPlan_reportPlanDescription :: Lens' ReportPlan (Maybe Text)
reportPlan_reportPlanDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReportPlan' {Maybe Text
reportPlanDescription :: Maybe Text
$sel:reportPlanDescription:ReportPlan' :: ReportPlan -> Maybe Text
reportPlanDescription} -> Maybe Text
reportPlanDescription) (\s :: ReportPlan
s@ReportPlan' {} Maybe Text
a -> ReportPlan
s {$sel:reportPlanDescription:ReportPlan' :: Maybe Text
reportPlanDescription = Maybe Text
a} :: ReportPlan)

-- | The unique name of the report plan. This name is between 1 and 256
-- characters starting with a letter, and consisting of letters (a-z, A-Z),
-- numbers (0-9), and underscores (_).
reportPlan_reportPlanName :: Lens.Lens' ReportPlan (Prelude.Maybe Prelude.Text)
reportPlan_reportPlanName :: Lens' ReportPlan (Maybe Text)
reportPlan_reportPlanName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReportPlan' {Maybe Text
reportPlanName :: Maybe Text
$sel:reportPlanName:ReportPlan' :: ReportPlan -> Maybe Text
reportPlanName} -> Maybe Text
reportPlanName) (\s :: ReportPlan
s@ReportPlan' {} Maybe Text
a -> ReportPlan
s {$sel:reportPlanName:ReportPlan' :: Maybe Text
reportPlanName = Maybe Text
a} :: ReportPlan)

-- | Identifies the report template for the report. Reports are built using a
-- report template. The report templates are:
--
-- @RESOURCE_COMPLIANCE_REPORT | CONTROL_COMPLIANCE_REPORT | BACKUP_JOB_REPORT | COPY_JOB_REPORT | RESTORE_JOB_REPORT@
--
-- If the report template is @RESOURCE_COMPLIANCE_REPORT@ or
-- @CONTROL_COMPLIANCE_REPORT@, this API resource also describes the report
-- coverage by Amazon Web Services Regions and frameworks.
reportPlan_reportSetting :: Lens.Lens' ReportPlan (Prelude.Maybe ReportSetting)
reportPlan_reportSetting :: Lens' ReportPlan (Maybe ReportSetting)
reportPlan_reportSetting = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReportPlan' {Maybe ReportSetting
reportSetting :: Maybe ReportSetting
$sel:reportSetting:ReportPlan' :: ReportPlan -> Maybe ReportSetting
reportSetting} -> Maybe ReportSetting
reportSetting) (\s :: ReportPlan
s@ReportPlan' {} Maybe ReportSetting
a -> ReportPlan
s {$sel:reportSetting:ReportPlan' :: Maybe ReportSetting
reportSetting = Maybe ReportSetting
a} :: ReportPlan)

instance Data.FromJSON ReportPlan where
  parseJSON :: Value -> Parser ReportPlan
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ReportPlan"
      ( \Object
x ->
          Maybe POSIX
-> Maybe Text
-> Maybe POSIX
-> Maybe POSIX
-> Maybe ReportDeliveryChannel
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe ReportSetting
-> ReportPlan
ReportPlan'
            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
"CreationTime")
            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
"DeploymentStatus")
            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
"LastAttemptedExecutionTime")
            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
"LastSuccessfulExecutionTime")
            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
"ReportDeliveryChannel")
            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
"ReportPlanArn")
            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
"ReportPlanDescription")
            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
"ReportPlanName")
            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
"ReportSetting")
      )

instance Prelude.Hashable ReportPlan where
  hashWithSalt :: Int -> ReportPlan -> Int
hashWithSalt Int
_salt ReportPlan' {Maybe Text
Maybe POSIX
Maybe ReportDeliveryChannel
Maybe ReportSetting
reportSetting :: Maybe ReportSetting
reportPlanName :: Maybe Text
reportPlanDescription :: Maybe Text
reportPlanArn :: Maybe Text
reportDeliveryChannel :: Maybe ReportDeliveryChannel
lastSuccessfulExecutionTime :: Maybe POSIX
lastAttemptedExecutionTime :: Maybe POSIX
deploymentStatus :: Maybe Text
creationTime :: Maybe POSIX
$sel:reportSetting:ReportPlan' :: ReportPlan -> Maybe ReportSetting
$sel:reportPlanName:ReportPlan' :: ReportPlan -> Maybe Text
$sel:reportPlanDescription:ReportPlan' :: ReportPlan -> Maybe Text
$sel:reportPlanArn:ReportPlan' :: ReportPlan -> Maybe Text
$sel:reportDeliveryChannel:ReportPlan' :: ReportPlan -> Maybe ReportDeliveryChannel
$sel:lastSuccessfulExecutionTime:ReportPlan' :: ReportPlan -> Maybe POSIX
$sel:lastAttemptedExecutionTime:ReportPlan' :: ReportPlan -> Maybe POSIX
$sel:deploymentStatus:ReportPlan' :: ReportPlan -> Maybe Text
$sel:creationTime:ReportPlan' :: ReportPlan -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
creationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
deploymentStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastAttemptedExecutionTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastSuccessfulExecutionTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ReportDeliveryChannel
reportDeliveryChannel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
reportPlanArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
reportPlanDescription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
reportPlanName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ReportSetting
reportSetting

instance Prelude.NFData ReportPlan where
  rnf :: ReportPlan -> ()
rnf ReportPlan' {Maybe Text
Maybe POSIX
Maybe ReportDeliveryChannel
Maybe ReportSetting
reportSetting :: Maybe ReportSetting
reportPlanName :: Maybe Text
reportPlanDescription :: Maybe Text
reportPlanArn :: Maybe Text
reportDeliveryChannel :: Maybe ReportDeliveryChannel
lastSuccessfulExecutionTime :: Maybe POSIX
lastAttemptedExecutionTime :: Maybe POSIX
deploymentStatus :: Maybe Text
creationTime :: Maybe POSIX
$sel:reportSetting:ReportPlan' :: ReportPlan -> Maybe ReportSetting
$sel:reportPlanName:ReportPlan' :: ReportPlan -> Maybe Text
$sel:reportPlanDescription:ReportPlan' :: ReportPlan -> Maybe Text
$sel:reportPlanArn:ReportPlan' :: ReportPlan -> Maybe Text
$sel:reportDeliveryChannel:ReportPlan' :: ReportPlan -> Maybe ReportDeliveryChannel
$sel:lastSuccessfulExecutionTime:ReportPlan' :: ReportPlan -> Maybe POSIX
$sel:lastAttemptedExecutionTime:ReportPlan' :: ReportPlan -> Maybe POSIX
$sel:deploymentStatus:ReportPlan' :: ReportPlan -> Maybe Text
$sel:creationTime:ReportPlan' :: ReportPlan -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
deploymentStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastAttemptedExecutionTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastSuccessfulExecutionTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ReportDeliveryChannel
reportDeliveryChannel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
reportPlanArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
reportPlanDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
reportPlanName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ReportSetting
reportSetting