{-# 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.Backup.UpdateReportPlan
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates an existing report plan identified by its @ReportPlanName@ with
-- the input document in JSON format.
module Amazonka.Backup.UpdateReportPlan
  ( -- * Creating a Request
    UpdateReportPlan (..),
    newUpdateReportPlan,

    -- * Request Lenses
    updateReportPlan_idempotencyToken,
    updateReportPlan_reportDeliveryChannel,
    updateReportPlan_reportPlanDescription,
    updateReportPlan_reportSetting,
    updateReportPlan_reportPlanName,

    -- * Destructuring the Response
    UpdateReportPlanResponse (..),
    newUpdateReportPlanResponse,

    -- * Response Lenses
    updateReportPlanResponse_creationTime,
    updateReportPlanResponse_reportPlanArn,
    updateReportPlanResponse_reportPlanName,
    updateReportPlanResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateReportPlan' smart constructor.
data UpdateReportPlan = UpdateReportPlan'
  { -- | A customer-chosen string that you can use to distinguish between
    -- otherwise identical calls to @UpdateReportPlanInput@. Retrying a
    -- successful request with the same idempotency token results in a success
    -- message with no action taken.
    UpdateReportPlan -> Maybe Text
idempotencyToken :: Prelude.Maybe Prelude.Text,
    -- | A structure that contains information about where to deliver your
    -- reports, specifically your Amazon S3 bucket name, S3 key prefix, and the
    -- formats of your reports.
    UpdateReportPlan -> Maybe ReportDeliveryChannel
reportDeliveryChannel :: Prelude.Maybe ReportDeliveryChannel,
    -- | An optional description of the report plan with a maximum 1,024
    -- characters.
    UpdateReportPlan -> Maybe Text
reportPlanDescription :: 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.
    UpdateReportPlan -> Maybe ReportSetting
reportSetting :: Prelude.Maybe ReportSetting,
    -- | 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 (_).
    UpdateReportPlan -> Text
reportPlanName :: Prelude.Text
  }
  deriving (UpdateReportPlan -> UpdateReportPlan -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateReportPlan -> UpdateReportPlan -> Bool
$c/= :: UpdateReportPlan -> UpdateReportPlan -> Bool
== :: UpdateReportPlan -> UpdateReportPlan -> Bool
$c== :: UpdateReportPlan -> UpdateReportPlan -> Bool
Prelude.Eq, ReadPrec [UpdateReportPlan]
ReadPrec UpdateReportPlan
Int -> ReadS UpdateReportPlan
ReadS [UpdateReportPlan]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateReportPlan]
$creadListPrec :: ReadPrec [UpdateReportPlan]
readPrec :: ReadPrec UpdateReportPlan
$creadPrec :: ReadPrec UpdateReportPlan
readList :: ReadS [UpdateReportPlan]
$creadList :: ReadS [UpdateReportPlan]
readsPrec :: Int -> ReadS UpdateReportPlan
$creadsPrec :: Int -> ReadS UpdateReportPlan
Prelude.Read, Int -> UpdateReportPlan -> ShowS
[UpdateReportPlan] -> ShowS
UpdateReportPlan -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateReportPlan] -> ShowS
$cshowList :: [UpdateReportPlan] -> ShowS
show :: UpdateReportPlan -> String
$cshow :: UpdateReportPlan -> String
showsPrec :: Int -> UpdateReportPlan -> ShowS
$cshowsPrec :: Int -> UpdateReportPlan -> ShowS
Prelude.Show, forall x. Rep UpdateReportPlan x -> UpdateReportPlan
forall x. UpdateReportPlan -> Rep UpdateReportPlan x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateReportPlan x -> UpdateReportPlan
$cfrom :: forall x. UpdateReportPlan -> Rep UpdateReportPlan x
Prelude.Generic)

-- |
-- Create a value of 'UpdateReportPlan' 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:
--
-- 'idempotencyToken', 'updateReportPlan_idempotencyToken' - A customer-chosen string that you can use to distinguish between
-- otherwise identical calls to @UpdateReportPlanInput@. Retrying a
-- successful request with the same idempotency token results in a success
-- message with no action taken.
--
-- 'reportDeliveryChannel', 'updateReportPlan_reportDeliveryChannel' - A structure that contains information about where to deliver your
-- reports, specifically your Amazon S3 bucket name, S3 key prefix, and the
-- formats of your reports.
--
-- 'reportPlanDescription', 'updateReportPlan_reportPlanDescription' - An optional description of the report plan with a maximum 1,024
-- characters.
--
-- 'reportSetting', 'updateReportPlan_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.
--
-- 'reportPlanName', 'updateReportPlan_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 (_).
newUpdateReportPlan ::
  -- | 'reportPlanName'
  Prelude.Text ->
  UpdateReportPlan
newUpdateReportPlan :: Text -> UpdateReportPlan
newUpdateReportPlan Text
pReportPlanName_ =
  UpdateReportPlan'
    { $sel:idempotencyToken:UpdateReportPlan' :: Maybe Text
idempotencyToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:reportDeliveryChannel:UpdateReportPlan' :: Maybe ReportDeliveryChannel
reportDeliveryChannel = forall a. Maybe a
Prelude.Nothing,
      $sel:reportPlanDescription:UpdateReportPlan' :: Maybe Text
reportPlanDescription = forall a. Maybe a
Prelude.Nothing,
      $sel:reportSetting:UpdateReportPlan' :: Maybe ReportSetting
reportSetting = forall a. Maybe a
Prelude.Nothing,
      $sel:reportPlanName:UpdateReportPlan' :: Text
reportPlanName = Text
pReportPlanName_
    }

-- | A customer-chosen string that you can use to distinguish between
-- otherwise identical calls to @UpdateReportPlanInput@. Retrying a
-- successful request with the same idempotency token results in a success
-- message with no action taken.
updateReportPlan_idempotencyToken :: Lens.Lens' UpdateReportPlan (Prelude.Maybe Prelude.Text)
updateReportPlan_idempotencyToken :: Lens' UpdateReportPlan (Maybe Text)
updateReportPlan_idempotencyToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateReportPlan' {Maybe Text
idempotencyToken :: Maybe Text
$sel:idempotencyToken:UpdateReportPlan' :: UpdateReportPlan -> Maybe Text
idempotencyToken} -> Maybe Text
idempotencyToken) (\s :: UpdateReportPlan
s@UpdateReportPlan' {} Maybe Text
a -> UpdateReportPlan
s {$sel:idempotencyToken:UpdateReportPlan' :: Maybe Text
idempotencyToken = Maybe Text
a} :: UpdateReportPlan)

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

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

-- | 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.
updateReportPlan_reportSetting :: Lens.Lens' UpdateReportPlan (Prelude.Maybe ReportSetting)
updateReportPlan_reportSetting :: Lens' UpdateReportPlan (Maybe ReportSetting)
updateReportPlan_reportSetting = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateReportPlan' {Maybe ReportSetting
reportSetting :: Maybe ReportSetting
$sel:reportSetting:UpdateReportPlan' :: UpdateReportPlan -> Maybe ReportSetting
reportSetting} -> Maybe ReportSetting
reportSetting) (\s :: UpdateReportPlan
s@UpdateReportPlan' {} Maybe ReportSetting
a -> UpdateReportPlan
s {$sel:reportSetting:UpdateReportPlan' :: Maybe ReportSetting
reportSetting = Maybe ReportSetting
a} :: UpdateReportPlan)

-- | 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 (_).
updateReportPlan_reportPlanName :: Lens.Lens' UpdateReportPlan Prelude.Text
updateReportPlan_reportPlanName :: Lens' UpdateReportPlan Text
updateReportPlan_reportPlanName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateReportPlan' {Text
reportPlanName :: Text
$sel:reportPlanName:UpdateReportPlan' :: UpdateReportPlan -> Text
reportPlanName} -> Text
reportPlanName) (\s :: UpdateReportPlan
s@UpdateReportPlan' {} Text
a -> UpdateReportPlan
s {$sel:reportPlanName:UpdateReportPlan' :: Text
reportPlanName = Text
a} :: UpdateReportPlan)

instance Core.AWSRequest UpdateReportPlan where
  type
    AWSResponse UpdateReportPlan =
      UpdateReportPlanResponse
  request :: (Service -> Service)
-> UpdateReportPlan -> Request UpdateReportPlan
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateReportPlan
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateReportPlan)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe POSIX
-> Maybe Text -> Maybe Text -> Int -> UpdateReportPlanResponse
UpdateReportPlanResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (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 -> Either String (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 -> Either String (Maybe a)
Data..?> Key
"ReportPlanName")
            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 UpdateReportPlan where
  hashWithSalt :: Int -> UpdateReportPlan -> Int
hashWithSalt Int
_salt UpdateReportPlan' {Maybe Text
Maybe ReportDeliveryChannel
Maybe ReportSetting
Text
reportPlanName :: Text
reportSetting :: Maybe ReportSetting
reportPlanDescription :: Maybe Text
reportDeliveryChannel :: Maybe ReportDeliveryChannel
idempotencyToken :: Maybe Text
$sel:reportPlanName:UpdateReportPlan' :: UpdateReportPlan -> Text
$sel:reportSetting:UpdateReportPlan' :: UpdateReportPlan -> Maybe ReportSetting
$sel:reportPlanDescription:UpdateReportPlan' :: UpdateReportPlan -> Maybe Text
$sel:reportDeliveryChannel:UpdateReportPlan' :: UpdateReportPlan -> Maybe ReportDeliveryChannel
$sel:idempotencyToken:UpdateReportPlan' :: UpdateReportPlan -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
idempotencyToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ReportDeliveryChannel
reportDeliveryChannel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
reportPlanDescription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ReportSetting
reportSetting
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
reportPlanName

instance Prelude.NFData UpdateReportPlan where
  rnf :: UpdateReportPlan -> ()
rnf UpdateReportPlan' {Maybe Text
Maybe ReportDeliveryChannel
Maybe ReportSetting
Text
reportPlanName :: Text
reportSetting :: Maybe ReportSetting
reportPlanDescription :: Maybe Text
reportDeliveryChannel :: Maybe ReportDeliveryChannel
idempotencyToken :: Maybe Text
$sel:reportPlanName:UpdateReportPlan' :: UpdateReportPlan -> Text
$sel:reportSetting:UpdateReportPlan' :: UpdateReportPlan -> Maybe ReportSetting
$sel:reportPlanDescription:UpdateReportPlan' :: UpdateReportPlan -> Maybe Text
$sel:reportDeliveryChannel:UpdateReportPlan' :: UpdateReportPlan -> Maybe ReportDeliveryChannel
$sel:idempotencyToken:UpdateReportPlan' :: UpdateReportPlan -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
idempotencyToken
      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
reportPlanDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ReportSetting
reportSetting
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
reportPlanName

instance Data.ToHeaders UpdateReportPlan where
  toHeaders :: UpdateReportPlan -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateReportPlan where
  toJSON :: UpdateReportPlan -> Value
toJSON UpdateReportPlan' {Maybe Text
Maybe ReportDeliveryChannel
Maybe ReportSetting
Text
reportPlanName :: Text
reportSetting :: Maybe ReportSetting
reportPlanDescription :: Maybe Text
reportDeliveryChannel :: Maybe ReportDeliveryChannel
idempotencyToken :: Maybe Text
$sel:reportPlanName:UpdateReportPlan' :: UpdateReportPlan -> Text
$sel:reportSetting:UpdateReportPlan' :: UpdateReportPlan -> Maybe ReportSetting
$sel:reportPlanDescription:UpdateReportPlan' :: UpdateReportPlan -> Maybe Text
$sel:reportDeliveryChannel:UpdateReportPlan' :: UpdateReportPlan -> Maybe ReportDeliveryChannel
$sel:idempotencyToken:UpdateReportPlan' :: UpdateReportPlan -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"IdempotencyToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
idempotencyToken,
            (Key
"ReportDeliveryChannel" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ReportDeliveryChannel
reportDeliveryChannel,
            (Key
"ReportPlanDescription" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
reportPlanDescription,
            (Key
"ReportSetting" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ReportSetting
reportSetting
          ]
      )

instance Data.ToPath UpdateReportPlan where
  toPath :: UpdateReportPlan -> ByteString
toPath UpdateReportPlan' {Maybe Text
Maybe ReportDeliveryChannel
Maybe ReportSetting
Text
reportPlanName :: Text
reportSetting :: Maybe ReportSetting
reportPlanDescription :: Maybe Text
reportDeliveryChannel :: Maybe ReportDeliveryChannel
idempotencyToken :: Maybe Text
$sel:reportPlanName:UpdateReportPlan' :: UpdateReportPlan -> Text
$sel:reportSetting:UpdateReportPlan' :: UpdateReportPlan -> Maybe ReportSetting
$sel:reportPlanDescription:UpdateReportPlan' :: UpdateReportPlan -> Maybe Text
$sel:reportDeliveryChannel:UpdateReportPlan' :: UpdateReportPlan -> Maybe ReportDeliveryChannel
$sel:idempotencyToken:UpdateReportPlan' :: UpdateReportPlan -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/audit/report-plans/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
reportPlanName]

instance Data.ToQuery UpdateReportPlan where
  toQuery :: UpdateReportPlan -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newUpdateReportPlanResponse' smart constructor.
data UpdateReportPlanResponse = UpdateReportPlanResponse'
  { -- | 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.
    UpdateReportPlanResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | An Amazon Resource Name (ARN) that uniquely identifies a resource. The
    -- format of the ARN depends on the resource type.
    UpdateReportPlanResponse -> Maybe Text
reportPlanArn :: Prelude.Maybe Prelude.Text,
    -- | The unique name of the report plan.
    UpdateReportPlanResponse -> Maybe Text
reportPlanName :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateReportPlanResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateReportPlanResponse -> UpdateReportPlanResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateReportPlanResponse -> UpdateReportPlanResponse -> Bool
$c/= :: UpdateReportPlanResponse -> UpdateReportPlanResponse -> Bool
== :: UpdateReportPlanResponse -> UpdateReportPlanResponse -> Bool
$c== :: UpdateReportPlanResponse -> UpdateReportPlanResponse -> Bool
Prelude.Eq, ReadPrec [UpdateReportPlanResponse]
ReadPrec UpdateReportPlanResponse
Int -> ReadS UpdateReportPlanResponse
ReadS [UpdateReportPlanResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateReportPlanResponse]
$creadListPrec :: ReadPrec [UpdateReportPlanResponse]
readPrec :: ReadPrec UpdateReportPlanResponse
$creadPrec :: ReadPrec UpdateReportPlanResponse
readList :: ReadS [UpdateReportPlanResponse]
$creadList :: ReadS [UpdateReportPlanResponse]
readsPrec :: Int -> ReadS UpdateReportPlanResponse
$creadsPrec :: Int -> ReadS UpdateReportPlanResponse
Prelude.Read, Int -> UpdateReportPlanResponse -> ShowS
[UpdateReportPlanResponse] -> ShowS
UpdateReportPlanResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateReportPlanResponse] -> ShowS
$cshowList :: [UpdateReportPlanResponse] -> ShowS
show :: UpdateReportPlanResponse -> String
$cshow :: UpdateReportPlanResponse -> String
showsPrec :: Int -> UpdateReportPlanResponse -> ShowS
$cshowsPrec :: Int -> UpdateReportPlanResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateReportPlanResponse x -> UpdateReportPlanResponse
forall x.
UpdateReportPlanResponse -> Rep UpdateReportPlanResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateReportPlanResponse x -> UpdateReportPlanResponse
$cfrom :: forall x.
UpdateReportPlanResponse -> Rep UpdateReportPlanResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateReportPlanResponse' 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', 'updateReportPlanResponse_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.
--
-- 'reportPlanArn', 'updateReportPlanResponse_reportPlanArn' - An Amazon Resource Name (ARN) that uniquely identifies a resource. The
-- format of the ARN depends on the resource type.
--
-- 'reportPlanName', 'updateReportPlanResponse_reportPlanName' - The unique name of the report plan.
--
-- 'httpStatus', 'updateReportPlanResponse_httpStatus' - The response's http status code.
newUpdateReportPlanResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateReportPlanResponse
newUpdateReportPlanResponse :: Int -> UpdateReportPlanResponse
newUpdateReportPlanResponse Int
pHttpStatus_ =
  UpdateReportPlanResponse'
    { $sel:creationTime:UpdateReportPlanResponse' :: Maybe POSIX
creationTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:reportPlanArn:UpdateReportPlanResponse' :: Maybe Text
reportPlanArn = forall a. Maybe a
Prelude.Nothing,
      $sel:reportPlanName:UpdateReportPlanResponse' :: Maybe Text
reportPlanName = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateReportPlanResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | 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.
updateReportPlanResponse_creationTime :: Lens.Lens' UpdateReportPlanResponse (Prelude.Maybe Prelude.UTCTime)
updateReportPlanResponse_creationTime :: Lens' UpdateReportPlanResponse (Maybe UTCTime)
updateReportPlanResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateReportPlanResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:UpdateReportPlanResponse' :: UpdateReportPlanResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: UpdateReportPlanResponse
s@UpdateReportPlanResponse' {} Maybe POSIX
a -> UpdateReportPlanResponse
s {$sel:creationTime:UpdateReportPlanResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: UpdateReportPlanResponse) 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

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

-- | The unique name of the report plan.
updateReportPlanResponse_reportPlanName :: Lens.Lens' UpdateReportPlanResponse (Prelude.Maybe Prelude.Text)
updateReportPlanResponse_reportPlanName :: Lens' UpdateReportPlanResponse (Maybe Text)
updateReportPlanResponse_reportPlanName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateReportPlanResponse' {Maybe Text
reportPlanName :: Maybe Text
$sel:reportPlanName:UpdateReportPlanResponse' :: UpdateReportPlanResponse -> Maybe Text
reportPlanName} -> Maybe Text
reportPlanName) (\s :: UpdateReportPlanResponse
s@UpdateReportPlanResponse' {} Maybe Text
a -> UpdateReportPlanResponse
s {$sel:reportPlanName:UpdateReportPlanResponse' :: Maybe Text
reportPlanName = Maybe Text
a} :: UpdateReportPlanResponse)

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

instance Prelude.NFData UpdateReportPlanResponse where
  rnf :: UpdateReportPlanResponse -> ()
rnf UpdateReportPlanResponse' {Int
Maybe Text
Maybe POSIX
httpStatus :: Int
reportPlanName :: Maybe Text
reportPlanArn :: Maybe Text
creationTime :: Maybe POSIX
$sel:httpStatus:UpdateReportPlanResponse' :: UpdateReportPlanResponse -> Int
$sel:reportPlanName:UpdateReportPlanResponse' :: UpdateReportPlanResponse -> Maybe Text
$sel:reportPlanArn:UpdateReportPlanResponse' :: UpdateReportPlanResponse -> Maybe Text
$sel:creationTime:UpdateReportPlanResponse' :: UpdateReportPlanResponse -> 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
reportPlanArn
      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 Int
httpStatus