{-# 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.Shield.Types.AttackDetail
-- 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.Shield.Types.AttackDetail 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.Shield.Types.AttackProperty
import Amazonka.Shield.Types.Mitigation
import Amazonka.Shield.Types.SubResourceSummary
import Amazonka.Shield.Types.SummarizedCounter

-- | The details of a DDoS attack.
--
-- /See:/ 'newAttackDetail' smart constructor.
data AttackDetail = AttackDetail'
  { -- | List of counters that describe the attack for the specified time period.
    AttackDetail -> Maybe [SummarizedCounter]
attackCounters :: Prelude.Maybe [SummarizedCounter],
    -- | The unique identifier (ID) of the attack.
    AttackDetail -> Maybe Text
attackId :: Prelude.Maybe Prelude.Text,
    -- | The array of objects that provide details of the Shield event.
    --
    -- For infrastructure layer events (L3 and L4 events), you can view metrics
    -- for top contributors in Amazon CloudWatch metrics. For more information,
    -- see
    -- <https://docs.aws.amazon.com/waf/latest/developerguide/monitoring-cloudwatch.html#set-ddos-alarms Shield metrics and alarms>
    -- in the /WAF Developer Guide/.
    AttackDetail -> Maybe [AttackProperty]
attackProperties :: Prelude.Maybe [AttackProperty],
    -- | The time the attack ended, in Unix time in seconds.
    AttackDetail -> Maybe POSIX
endTime :: Prelude.Maybe Data.POSIX,
    -- | List of mitigation actions taken for the attack.
    AttackDetail -> Maybe [Mitigation]
mitigations :: Prelude.Maybe [Mitigation],
    -- | The ARN (Amazon Resource Name) of the resource that was attacked.
    AttackDetail -> Maybe Text
resourceArn :: Prelude.Maybe Prelude.Text,
    -- | The time the attack started, in Unix time in seconds.
    AttackDetail -> Maybe POSIX
startTime :: Prelude.Maybe Data.POSIX,
    -- | If applicable, additional detail about the resource being attacked, for
    -- example, IP address or URL.
    AttackDetail -> Maybe [SubResourceSummary]
subResources :: Prelude.Maybe [SubResourceSummary]
  }
  deriving (AttackDetail -> AttackDetail -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttackDetail -> AttackDetail -> Bool
$c/= :: AttackDetail -> AttackDetail -> Bool
== :: AttackDetail -> AttackDetail -> Bool
$c== :: AttackDetail -> AttackDetail -> Bool
Prelude.Eq, ReadPrec [AttackDetail]
ReadPrec AttackDetail
Int -> ReadS AttackDetail
ReadS [AttackDetail]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AttackDetail]
$creadListPrec :: ReadPrec [AttackDetail]
readPrec :: ReadPrec AttackDetail
$creadPrec :: ReadPrec AttackDetail
readList :: ReadS [AttackDetail]
$creadList :: ReadS [AttackDetail]
readsPrec :: Int -> ReadS AttackDetail
$creadsPrec :: Int -> ReadS AttackDetail
Prelude.Read, Int -> AttackDetail -> ShowS
[AttackDetail] -> ShowS
AttackDetail -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttackDetail] -> ShowS
$cshowList :: [AttackDetail] -> ShowS
show :: AttackDetail -> String
$cshow :: AttackDetail -> String
showsPrec :: Int -> AttackDetail -> ShowS
$cshowsPrec :: Int -> AttackDetail -> ShowS
Prelude.Show, forall x. Rep AttackDetail x -> AttackDetail
forall x. AttackDetail -> Rep AttackDetail x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AttackDetail x -> AttackDetail
$cfrom :: forall x. AttackDetail -> Rep AttackDetail x
Prelude.Generic)

-- |
-- Create a value of 'AttackDetail' 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:
--
-- 'attackCounters', 'attackDetail_attackCounters' - List of counters that describe the attack for the specified time period.
--
-- 'attackId', 'attackDetail_attackId' - The unique identifier (ID) of the attack.
--
-- 'attackProperties', 'attackDetail_attackProperties' - The array of objects that provide details of the Shield event.
--
-- For infrastructure layer events (L3 and L4 events), you can view metrics
-- for top contributors in Amazon CloudWatch metrics. For more information,
-- see
-- <https://docs.aws.amazon.com/waf/latest/developerguide/monitoring-cloudwatch.html#set-ddos-alarms Shield metrics and alarms>
-- in the /WAF Developer Guide/.
--
-- 'endTime', 'attackDetail_endTime' - The time the attack ended, in Unix time in seconds.
--
-- 'mitigations', 'attackDetail_mitigations' - List of mitigation actions taken for the attack.
--
-- 'resourceArn', 'attackDetail_resourceArn' - The ARN (Amazon Resource Name) of the resource that was attacked.
--
-- 'startTime', 'attackDetail_startTime' - The time the attack started, in Unix time in seconds.
--
-- 'subResources', 'attackDetail_subResources' - If applicable, additional detail about the resource being attacked, for
-- example, IP address or URL.
newAttackDetail ::
  AttackDetail
newAttackDetail :: AttackDetail
newAttackDetail =
  AttackDetail'
    { $sel:attackCounters:AttackDetail' :: Maybe [SummarizedCounter]
attackCounters = forall a. Maybe a
Prelude.Nothing,
      $sel:attackId:AttackDetail' :: Maybe Text
attackId = forall a. Maybe a
Prelude.Nothing,
      $sel:attackProperties:AttackDetail' :: Maybe [AttackProperty]
attackProperties = forall a. Maybe a
Prelude.Nothing,
      $sel:endTime:AttackDetail' :: Maybe POSIX
endTime = forall a. Maybe a
Prelude.Nothing,
      $sel:mitigations:AttackDetail' :: Maybe [Mitigation]
mitigations = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceArn:AttackDetail' :: Maybe Text
resourceArn = forall a. Maybe a
Prelude.Nothing,
      $sel:startTime:AttackDetail' :: Maybe POSIX
startTime = forall a. Maybe a
Prelude.Nothing,
      $sel:subResources:AttackDetail' :: Maybe [SubResourceSummary]
subResources = forall a. Maybe a
Prelude.Nothing
    }

-- | List of counters that describe the attack for the specified time period.
attackDetail_attackCounters :: Lens.Lens' AttackDetail (Prelude.Maybe [SummarizedCounter])
attackDetail_attackCounters :: Lens' AttackDetail (Maybe [SummarizedCounter])
attackDetail_attackCounters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttackDetail' {Maybe [SummarizedCounter]
attackCounters :: Maybe [SummarizedCounter]
$sel:attackCounters:AttackDetail' :: AttackDetail -> Maybe [SummarizedCounter]
attackCounters} -> Maybe [SummarizedCounter]
attackCounters) (\s :: AttackDetail
s@AttackDetail' {} Maybe [SummarizedCounter]
a -> AttackDetail
s {$sel:attackCounters:AttackDetail' :: Maybe [SummarizedCounter]
attackCounters = Maybe [SummarizedCounter]
a} :: AttackDetail) 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 unique identifier (ID) of the attack.
attackDetail_attackId :: Lens.Lens' AttackDetail (Prelude.Maybe Prelude.Text)
attackDetail_attackId :: Lens' AttackDetail (Maybe Text)
attackDetail_attackId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttackDetail' {Maybe Text
attackId :: Maybe Text
$sel:attackId:AttackDetail' :: AttackDetail -> Maybe Text
attackId} -> Maybe Text
attackId) (\s :: AttackDetail
s@AttackDetail' {} Maybe Text
a -> AttackDetail
s {$sel:attackId:AttackDetail' :: Maybe Text
attackId = Maybe Text
a} :: AttackDetail)

-- | The array of objects that provide details of the Shield event.
--
-- For infrastructure layer events (L3 and L4 events), you can view metrics
-- for top contributors in Amazon CloudWatch metrics. For more information,
-- see
-- <https://docs.aws.amazon.com/waf/latest/developerguide/monitoring-cloudwatch.html#set-ddos-alarms Shield metrics and alarms>
-- in the /WAF Developer Guide/.
attackDetail_attackProperties :: Lens.Lens' AttackDetail (Prelude.Maybe [AttackProperty])
attackDetail_attackProperties :: Lens' AttackDetail (Maybe [AttackProperty])
attackDetail_attackProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttackDetail' {Maybe [AttackProperty]
attackProperties :: Maybe [AttackProperty]
$sel:attackProperties:AttackDetail' :: AttackDetail -> Maybe [AttackProperty]
attackProperties} -> Maybe [AttackProperty]
attackProperties) (\s :: AttackDetail
s@AttackDetail' {} Maybe [AttackProperty]
a -> AttackDetail
s {$sel:attackProperties:AttackDetail' :: Maybe [AttackProperty]
attackProperties = Maybe [AttackProperty]
a} :: AttackDetail) 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 time the attack ended, in Unix time in seconds.
attackDetail_endTime :: Lens.Lens' AttackDetail (Prelude.Maybe Prelude.UTCTime)
attackDetail_endTime :: Lens' AttackDetail (Maybe UTCTime)
attackDetail_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttackDetail' {Maybe POSIX
endTime :: Maybe POSIX
$sel:endTime:AttackDetail' :: AttackDetail -> Maybe POSIX
endTime} -> Maybe POSIX
endTime) (\s :: AttackDetail
s@AttackDetail' {} Maybe POSIX
a -> AttackDetail
s {$sel:endTime:AttackDetail' :: Maybe POSIX
endTime = Maybe POSIX
a} :: AttackDetail) 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

-- | List of mitigation actions taken for the attack.
attackDetail_mitigations :: Lens.Lens' AttackDetail (Prelude.Maybe [Mitigation])
attackDetail_mitigations :: Lens' AttackDetail (Maybe [Mitigation])
attackDetail_mitigations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttackDetail' {Maybe [Mitigation]
mitigations :: Maybe [Mitigation]
$sel:mitigations:AttackDetail' :: AttackDetail -> Maybe [Mitigation]
mitigations} -> Maybe [Mitigation]
mitigations) (\s :: AttackDetail
s@AttackDetail' {} Maybe [Mitigation]
a -> AttackDetail
s {$sel:mitigations:AttackDetail' :: Maybe [Mitigation]
mitigations = Maybe [Mitigation]
a} :: AttackDetail) 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 ARN (Amazon Resource Name) of the resource that was attacked.
attackDetail_resourceArn :: Lens.Lens' AttackDetail (Prelude.Maybe Prelude.Text)
attackDetail_resourceArn :: Lens' AttackDetail (Maybe Text)
attackDetail_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttackDetail' {Maybe Text
resourceArn :: Maybe Text
$sel:resourceArn:AttackDetail' :: AttackDetail -> Maybe Text
resourceArn} -> Maybe Text
resourceArn) (\s :: AttackDetail
s@AttackDetail' {} Maybe Text
a -> AttackDetail
s {$sel:resourceArn:AttackDetail' :: Maybe Text
resourceArn = Maybe Text
a} :: AttackDetail)

-- | The time the attack started, in Unix time in seconds.
attackDetail_startTime :: Lens.Lens' AttackDetail (Prelude.Maybe Prelude.UTCTime)
attackDetail_startTime :: Lens' AttackDetail (Maybe UTCTime)
attackDetail_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttackDetail' {Maybe POSIX
startTime :: Maybe POSIX
$sel:startTime:AttackDetail' :: AttackDetail -> Maybe POSIX
startTime} -> Maybe POSIX
startTime) (\s :: AttackDetail
s@AttackDetail' {} Maybe POSIX
a -> AttackDetail
s {$sel:startTime:AttackDetail' :: Maybe POSIX
startTime = Maybe POSIX
a} :: AttackDetail) 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

-- | If applicable, additional detail about the resource being attacked, for
-- example, IP address or URL.
attackDetail_subResources :: Lens.Lens' AttackDetail (Prelude.Maybe [SubResourceSummary])
attackDetail_subResources :: Lens' AttackDetail (Maybe [SubResourceSummary])
attackDetail_subResources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttackDetail' {Maybe [SubResourceSummary]
subResources :: Maybe [SubResourceSummary]
$sel:subResources:AttackDetail' :: AttackDetail -> Maybe [SubResourceSummary]
subResources} -> Maybe [SubResourceSummary]
subResources) (\s :: AttackDetail
s@AttackDetail' {} Maybe [SubResourceSummary]
a -> AttackDetail
s {$sel:subResources:AttackDetail' :: Maybe [SubResourceSummary]
subResources = Maybe [SubResourceSummary]
a} :: AttackDetail) 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

instance Data.FromJSON AttackDetail where
  parseJSON :: Value -> Parser AttackDetail
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"AttackDetail"
      ( \Object
x ->
          Maybe [SummarizedCounter]
-> Maybe Text
-> Maybe [AttackProperty]
-> Maybe POSIX
-> Maybe [Mitigation]
-> Maybe Text
-> Maybe POSIX
-> Maybe [SubResourceSummary]
-> AttackDetail
AttackDetail'
            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
"AttackCounters" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            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
"AttackId")
            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
"AttackProperties"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            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
"EndTime")
            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
"Mitigations" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            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
"ResourceArn")
            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
"StartTime")
            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
"SubResources" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
      )

instance Prelude.Hashable AttackDetail where
  hashWithSalt :: Int -> AttackDetail -> Int
hashWithSalt Int
_salt AttackDetail' {Maybe [Mitigation]
Maybe [SummarizedCounter]
Maybe [SubResourceSummary]
Maybe [AttackProperty]
Maybe Text
Maybe POSIX
subResources :: Maybe [SubResourceSummary]
startTime :: Maybe POSIX
resourceArn :: Maybe Text
mitigations :: Maybe [Mitigation]
endTime :: Maybe POSIX
attackProperties :: Maybe [AttackProperty]
attackId :: Maybe Text
attackCounters :: Maybe [SummarizedCounter]
$sel:subResources:AttackDetail' :: AttackDetail -> Maybe [SubResourceSummary]
$sel:startTime:AttackDetail' :: AttackDetail -> Maybe POSIX
$sel:resourceArn:AttackDetail' :: AttackDetail -> Maybe Text
$sel:mitigations:AttackDetail' :: AttackDetail -> Maybe [Mitigation]
$sel:endTime:AttackDetail' :: AttackDetail -> Maybe POSIX
$sel:attackProperties:AttackDetail' :: AttackDetail -> Maybe [AttackProperty]
$sel:attackId:AttackDetail' :: AttackDetail -> Maybe Text
$sel:attackCounters:AttackDetail' :: AttackDetail -> Maybe [SummarizedCounter]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [SummarizedCounter]
attackCounters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
attackId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [AttackProperty]
attackProperties
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
endTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Mitigation]
mitigations
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
startTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [SubResourceSummary]
subResources

instance Prelude.NFData AttackDetail where
  rnf :: AttackDetail -> ()
rnf AttackDetail' {Maybe [Mitigation]
Maybe [SummarizedCounter]
Maybe [SubResourceSummary]
Maybe [AttackProperty]
Maybe Text
Maybe POSIX
subResources :: Maybe [SubResourceSummary]
startTime :: Maybe POSIX
resourceArn :: Maybe Text
mitigations :: Maybe [Mitigation]
endTime :: Maybe POSIX
attackProperties :: Maybe [AttackProperty]
attackId :: Maybe Text
attackCounters :: Maybe [SummarizedCounter]
$sel:subResources:AttackDetail' :: AttackDetail -> Maybe [SubResourceSummary]
$sel:startTime:AttackDetail' :: AttackDetail -> Maybe POSIX
$sel:resourceArn:AttackDetail' :: AttackDetail -> Maybe Text
$sel:mitigations:AttackDetail' :: AttackDetail -> Maybe [Mitigation]
$sel:endTime:AttackDetail' :: AttackDetail -> Maybe POSIX
$sel:attackProperties:AttackDetail' :: AttackDetail -> Maybe [AttackProperty]
$sel:attackId:AttackDetail' :: AttackDetail -> Maybe Text
$sel:attackCounters:AttackDetail' :: AttackDetail -> Maybe [SummarizedCounter]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [SummarizedCounter]
attackCounters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
attackId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [AttackProperty]
attackProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
endTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Mitigation]
mitigations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
resourceArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
startTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [SubResourceSummary]
subResources