{-# 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.IoT.Types.TopicRuleDestinationSummary
-- 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.IoT.Types.TopicRuleDestinationSummary where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.IoT.Types.HttpUrlDestinationSummary
import Amazonka.IoT.Types.TopicRuleDestinationStatus
import Amazonka.IoT.Types.VpcDestinationSummary
import qualified Amazonka.Prelude as Prelude

-- | Information about the topic rule destination.
--
-- /See:/ 'newTopicRuleDestinationSummary' smart constructor.
data TopicRuleDestinationSummary = TopicRuleDestinationSummary'
  { -- | The topic rule destination ARN.
    TopicRuleDestinationSummary -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The date and time when the topic rule destination was created.
    TopicRuleDestinationSummary -> Maybe POSIX
createdAt :: Prelude.Maybe Data.POSIX,
    -- | Information about the HTTP URL.
    TopicRuleDestinationSummary -> Maybe HttpUrlDestinationSummary
httpUrlSummary :: Prelude.Maybe HttpUrlDestinationSummary,
    -- | The date and time when the topic rule destination was last updated.
    TopicRuleDestinationSummary -> Maybe POSIX
lastUpdatedAt :: Prelude.Maybe Data.POSIX,
    -- | The status of the topic rule destination. Valid values are:
    --
    -- [IN_PROGRESS]
    --     A topic rule destination was created but has not been confirmed. You
    --     can set @status@ to @IN_PROGRESS@ by calling
    --     @UpdateTopicRuleDestination@. Calling @UpdateTopicRuleDestination@
    --     causes a new confirmation challenge to be sent to your confirmation
    --     endpoint.
    --
    -- [ENABLED]
    --     Confirmation was completed, and traffic to this destination is
    --     allowed. You can set @status@ to @DISABLED@ by calling
    --     @UpdateTopicRuleDestination@.
    --
    -- [DISABLED]
    --     Confirmation was completed, and traffic to this destination is not
    --     allowed. You can set @status@ to @ENABLED@ by calling
    --     @UpdateTopicRuleDestination@.
    --
    -- [ERROR]
    --     Confirmation could not be completed, for example if the confirmation
    --     timed out. You can call @GetTopicRuleDestination@ for details about
    --     the error. You can set @status@ to @IN_PROGRESS@ by calling
    --     @UpdateTopicRuleDestination@. Calling @UpdateTopicRuleDestination@
    --     causes a new confirmation challenge to be sent to your confirmation
    --     endpoint.
    TopicRuleDestinationSummary -> Maybe TopicRuleDestinationStatus
status :: Prelude.Maybe TopicRuleDestinationStatus,
    -- | The reason the topic rule destination is in the current status.
    TopicRuleDestinationSummary -> Maybe Text
statusReason :: Prelude.Maybe Prelude.Text,
    -- | Information about the virtual private cloud (VPC) connection.
    TopicRuleDestinationSummary -> Maybe VpcDestinationSummary
vpcDestinationSummary :: Prelude.Maybe VpcDestinationSummary
  }
  deriving (TopicRuleDestinationSummary -> TopicRuleDestinationSummary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TopicRuleDestinationSummary -> TopicRuleDestinationSummary -> Bool
$c/= :: TopicRuleDestinationSummary -> TopicRuleDestinationSummary -> Bool
== :: TopicRuleDestinationSummary -> TopicRuleDestinationSummary -> Bool
$c== :: TopicRuleDestinationSummary -> TopicRuleDestinationSummary -> Bool
Prelude.Eq, ReadPrec [TopicRuleDestinationSummary]
ReadPrec TopicRuleDestinationSummary
Int -> ReadS TopicRuleDestinationSummary
ReadS [TopicRuleDestinationSummary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TopicRuleDestinationSummary]
$creadListPrec :: ReadPrec [TopicRuleDestinationSummary]
readPrec :: ReadPrec TopicRuleDestinationSummary
$creadPrec :: ReadPrec TopicRuleDestinationSummary
readList :: ReadS [TopicRuleDestinationSummary]
$creadList :: ReadS [TopicRuleDestinationSummary]
readsPrec :: Int -> ReadS TopicRuleDestinationSummary
$creadsPrec :: Int -> ReadS TopicRuleDestinationSummary
Prelude.Read, Int -> TopicRuleDestinationSummary -> ShowS
[TopicRuleDestinationSummary] -> ShowS
TopicRuleDestinationSummary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TopicRuleDestinationSummary] -> ShowS
$cshowList :: [TopicRuleDestinationSummary] -> ShowS
show :: TopicRuleDestinationSummary -> String
$cshow :: TopicRuleDestinationSummary -> String
showsPrec :: Int -> TopicRuleDestinationSummary -> ShowS
$cshowsPrec :: Int -> TopicRuleDestinationSummary -> ShowS
Prelude.Show, forall x.
Rep TopicRuleDestinationSummary x -> TopicRuleDestinationSummary
forall x.
TopicRuleDestinationSummary -> Rep TopicRuleDestinationSummary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep TopicRuleDestinationSummary x -> TopicRuleDestinationSummary
$cfrom :: forall x.
TopicRuleDestinationSummary -> Rep TopicRuleDestinationSummary x
Prelude.Generic)

-- |
-- Create a value of 'TopicRuleDestinationSummary' 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:
--
-- 'arn', 'topicRuleDestinationSummary_arn' - The topic rule destination ARN.
--
-- 'createdAt', 'topicRuleDestinationSummary_createdAt' - The date and time when the topic rule destination was created.
--
-- 'httpUrlSummary', 'topicRuleDestinationSummary_httpUrlSummary' - Information about the HTTP URL.
--
-- 'lastUpdatedAt', 'topicRuleDestinationSummary_lastUpdatedAt' - The date and time when the topic rule destination was last updated.
--
-- 'status', 'topicRuleDestinationSummary_status' - The status of the topic rule destination. Valid values are:
--
-- [IN_PROGRESS]
--     A topic rule destination was created but has not been confirmed. You
--     can set @status@ to @IN_PROGRESS@ by calling
--     @UpdateTopicRuleDestination@. Calling @UpdateTopicRuleDestination@
--     causes a new confirmation challenge to be sent to your confirmation
--     endpoint.
--
-- [ENABLED]
--     Confirmation was completed, and traffic to this destination is
--     allowed. You can set @status@ to @DISABLED@ by calling
--     @UpdateTopicRuleDestination@.
--
-- [DISABLED]
--     Confirmation was completed, and traffic to this destination is not
--     allowed. You can set @status@ to @ENABLED@ by calling
--     @UpdateTopicRuleDestination@.
--
-- [ERROR]
--     Confirmation could not be completed, for example if the confirmation
--     timed out. You can call @GetTopicRuleDestination@ for details about
--     the error. You can set @status@ to @IN_PROGRESS@ by calling
--     @UpdateTopicRuleDestination@. Calling @UpdateTopicRuleDestination@
--     causes a new confirmation challenge to be sent to your confirmation
--     endpoint.
--
-- 'statusReason', 'topicRuleDestinationSummary_statusReason' - The reason the topic rule destination is in the current status.
--
-- 'vpcDestinationSummary', 'topicRuleDestinationSummary_vpcDestinationSummary' - Information about the virtual private cloud (VPC) connection.
newTopicRuleDestinationSummary ::
  TopicRuleDestinationSummary
newTopicRuleDestinationSummary :: TopicRuleDestinationSummary
newTopicRuleDestinationSummary =
  TopicRuleDestinationSummary'
    { $sel:arn:TopicRuleDestinationSummary' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:createdAt:TopicRuleDestinationSummary' :: Maybe POSIX
createdAt = forall a. Maybe a
Prelude.Nothing,
      $sel:httpUrlSummary:TopicRuleDestinationSummary' :: Maybe HttpUrlDestinationSummary
httpUrlSummary = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedAt:TopicRuleDestinationSummary' :: Maybe POSIX
lastUpdatedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:status:TopicRuleDestinationSummary' :: Maybe TopicRuleDestinationStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:statusReason:TopicRuleDestinationSummary' :: Maybe Text
statusReason = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcDestinationSummary:TopicRuleDestinationSummary' :: Maybe VpcDestinationSummary
vpcDestinationSummary = forall a. Maybe a
Prelude.Nothing
    }

-- | The topic rule destination ARN.
topicRuleDestinationSummary_arn :: Lens.Lens' TopicRuleDestinationSummary (Prelude.Maybe Prelude.Text)
topicRuleDestinationSummary_arn :: Lens' TopicRuleDestinationSummary (Maybe Text)
topicRuleDestinationSummary_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TopicRuleDestinationSummary' {Maybe Text
arn :: Maybe Text
$sel:arn:TopicRuleDestinationSummary' :: TopicRuleDestinationSummary -> Maybe Text
arn} -> Maybe Text
arn) (\s :: TopicRuleDestinationSummary
s@TopicRuleDestinationSummary' {} Maybe Text
a -> TopicRuleDestinationSummary
s {$sel:arn:TopicRuleDestinationSummary' :: Maybe Text
arn = Maybe Text
a} :: TopicRuleDestinationSummary)

-- | The date and time when the topic rule destination was created.
topicRuleDestinationSummary_createdAt :: Lens.Lens' TopicRuleDestinationSummary (Prelude.Maybe Prelude.UTCTime)
topicRuleDestinationSummary_createdAt :: Lens' TopicRuleDestinationSummary (Maybe UTCTime)
topicRuleDestinationSummary_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TopicRuleDestinationSummary' {Maybe POSIX
createdAt :: Maybe POSIX
$sel:createdAt:TopicRuleDestinationSummary' :: TopicRuleDestinationSummary -> Maybe POSIX
createdAt} -> Maybe POSIX
createdAt) (\s :: TopicRuleDestinationSummary
s@TopicRuleDestinationSummary' {} Maybe POSIX
a -> TopicRuleDestinationSummary
s {$sel:createdAt:TopicRuleDestinationSummary' :: Maybe POSIX
createdAt = Maybe POSIX
a} :: TopicRuleDestinationSummary) 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

-- | Information about the HTTP URL.
topicRuleDestinationSummary_httpUrlSummary :: Lens.Lens' TopicRuleDestinationSummary (Prelude.Maybe HttpUrlDestinationSummary)
topicRuleDestinationSummary_httpUrlSummary :: Lens' TopicRuleDestinationSummary (Maybe HttpUrlDestinationSummary)
topicRuleDestinationSummary_httpUrlSummary = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TopicRuleDestinationSummary' {Maybe HttpUrlDestinationSummary
httpUrlSummary :: Maybe HttpUrlDestinationSummary
$sel:httpUrlSummary:TopicRuleDestinationSummary' :: TopicRuleDestinationSummary -> Maybe HttpUrlDestinationSummary
httpUrlSummary} -> Maybe HttpUrlDestinationSummary
httpUrlSummary) (\s :: TopicRuleDestinationSummary
s@TopicRuleDestinationSummary' {} Maybe HttpUrlDestinationSummary
a -> TopicRuleDestinationSummary
s {$sel:httpUrlSummary:TopicRuleDestinationSummary' :: Maybe HttpUrlDestinationSummary
httpUrlSummary = Maybe HttpUrlDestinationSummary
a} :: TopicRuleDestinationSummary)

-- | The date and time when the topic rule destination was last updated.
topicRuleDestinationSummary_lastUpdatedAt :: Lens.Lens' TopicRuleDestinationSummary (Prelude.Maybe Prelude.UTCTime)
topicRuleDestinationSummary_lastUpdatedAt :: Lens' TopicRuleDestinationSummary (Maybe UTCTime)
topicRuleDestinationSummary_lastUpdatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TopicRuleDestinationSummary' {Maybe POSIX
lastUpdatedAt :: Maybe POSIX
$sel:lastUpdatedAt:TopicRuleDestinationSummary' :: TopicRuleDestinationSummary -> Maybe POSIX
lastUpdatedAt} -> Maybe POSIX
lastUpdatedAt) (\s :: TopicRuleDestinationSummary
s@TopicRuleDestinationSummary' {} Maybe POSIX
a -> TopicRuleDestinationSummary
s {$sel:lastUpdatedAt:TopicRuleDestinationSummary' :: Maybe POSIX
lastUpdatedAt = Maybe POSIX
a} :: TopicRuleDestinationSummary) 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 topic rule destination. Valid values are:
--
-- [IN_PROGRESS]
--     A topic rule destination was created but has not been confirmed. You
--     can set @status@ to @IN_PROGRESS@ by calling
--     @UpdateTopicRuleDestination@. Calling @UpdateTopicRuleDestination@
--     causes a new confirmation challenge to be sent to your confirmation
--     endpoint.
--
-- [ENABLED]
--     Confirmation was completed, and traffic to this destination is
--     allowed. You can set @status@ to @DISABLED@ by calling
--     @UpdateTopicRuleDestination@.
--
-- [DISABLED]
--     Confirmation was completed, and traffic to this destination is not
--     allowed. You can set @status@ to @ENABLED@ by calling
--     @UpdateTopicRuleDestination@.
--
-- [ERROR]
--     Confirmation could not be completed, for example if the confirmation
--     timed out. You can call @GetTopicRuleDestination@ for details about
--     the error. You can set @status@ to @IN_PROGRESS@ by calling
--     @UpdateTopicRuleDestination@. Calling @UpdateTopicRuleDestination@
--     causes a new confirmation challenge to be sent to your confirmation
--     endpoint.
topicRuleDestinationSummary_status :: Lens.Lens' TopicRuleDestinationSummary (Prelude.Maybe TopicRuleDestinationStatus)
topicRuleDestinationSummary_status :: Lens'
  TopicRuleDestinationSummary (Maybe TopicRuleDestinationStatus)
topicRuleDestinationSummary_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TopicRuleDestinationSummary' {Maybe TopicRuleDestinationStatus
status :: Maybe TopicRuleDestinationStatus
$sel:status:TopicRuleDestinationSummary' :: TopicRuleDestinationSummary -> Maybe TopicRuleDestinationStatus
status} -> Maybe TopicRuleDestinationStatus
status) (\s :: TopicRuleDestinationSummary
s@TopicRuleDestinationSummary' {} Maybe TopicRuleDestinationStatus
a -> TopicRuleDestinationSummary
s {$sel:status:TopicRuleDestinationSummary' :: Maybe TopicRuleDestinationStatus
status = Maybe TopicRuleDestinationStatus
a} :: TopicRuleDestinationSummary)

-- | The reason the topic rule destination is in the current status.
topicRuleDestinationSummary_statusReason :: Lens.Lens' TopicRuleDestinationSummary (Prelude.Maybe Prelude.Text)
topicRuleDestinationSummary_statusReason :: Lens' TopicRuleDestinationSummary (Maybe Text)
topicRuleDestinationSummary_statusReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TopicRuleDestinationSummary' {Maybe Text
statusReason :: Maybe Text
$sel:statusReason:TopicRuleDestinationSummary' :: TopicRuleDestinationSummary -> Maybe Text
statusReason} -> Maybe Text
statusReason) (\s :: TopicRuleDestinationSummary
s@TopicRuleDestinationSummary' {} Maybe Text
a -> TopicRuleDestinationSummary
s {$sel:statusReason:TopicRuleDestinationSummary' :: Maybe Text
statusReason = Maybe Text
a} :: TopicRuleDestinationSummary)

-- | Information about the virtual private cloud (VPC) connection.
topicRuleDestinationSummary_vpcDestinationSummary :: Lens.Lens' TopicRuleDestinationSummary (Prelude.Maybe VpcDestinationSummary)
topicRuleDestinationSummary_vpcDestinationSummary :: Lens' TopicRuleDestinationSummary (Maybe VpcDestinationSummary)
topicRuleDestinationSummary_vpcDestinationSummary = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TopicRuleDestinationSummary' {Maybe VpcDestinationSummary
vpcDestinationSummary :: Maybe VpcDestinationSummary
$sel:vpcDestinationSummary:TopicRuleDestinationSummary' :: TopicRuleDestinationSummary -> Maybe VpcDestinationSummary
vpcDestinationSummary} -> Maybe VpcDestinationSummary
vpcDestinationSummary) (\s :: TopicRuleDestinationSummary
s@TopicRuleDestinationSummary' {} Maybe VpcDestinationSummary
a -> TopicRuleDestinationSummary
s {$sel:vpcDestinationSummary:TopicRuleDestinationSummary' :: Maybe VpcDestinationSummary
vpcDestinationSummary = Maybe VpcDestinationSummary
a} :: TopicRuleDestinationSummary)

instance Data.FromJSON TopicRuleDestinationSummary where
  parseJSON :: Value -> Parser TopicRuleDestinationSummary
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"TopicRuleDestinationSummary"
      ( \Object
x ->
          Maybe Text
-> Maybe POSIX
-> Maybe HttpUrlDestinationSummary
-> Maybe POSIX
-> Maybe TopicRuleDestinationStatus
-> Maybe Text
-> Maybe VpcDestinationSummary
-> TopicRuleDestinationSummary
TopicRuleDestinationSummary'
            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
"arn")
            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
"createdAt")
            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
"httpUrlSummary")
            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
"lastUpdatedAt")
            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
"status")
            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
"statusReason")
            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
"vpcDestinationSummary")
      )

instance Prelude.Hashable TopicRuleDestinationSummary where
  hashWithSalt :: Int -> TopicRuleDestinationSummary -> Int
hashWithSalt Int
_salt TopicRuleDestinationSummary' {Maybe Text
Maybe POSIX
Maybe HttpUrlDestinationSummary
Maybe TopicRuleDestinationStatus
Maybe VpcDestinationSummary
vpcDestinationSummary :: Maybe VpcDestinationSummary
statusReason :: Maybe Text
status :: Maybe TopicRuleDestinationStatus
lastUpdatedAt :: Maybe POSIX
httpUrlSummary :: Maybe HttpUrlDestinationSummary
createdAt :: Maybe POSIX
arn :: Maybe Text
$sel:vpcDestinationSummary:TopicRuleDestinationSummary' :: TopicRuleDestinationSummary -> Maybe VpcDestinationSummary
$sel:statusReason:TopicRuleDestinationSummary' :: TopicRuleDestinationSummary -> Maybe Text
$sel:status:TopicRuleDestinationSummary' :: TopicRuleDestinationSummary -> Maybe TopicRuleDestinationStatus
$sel:lastUpdatedAt:TopicRuleDestinationSummary' :: TopicRuleDestinationSummary -> Maybe POSIX
$sel:httpUrlSummary:TopicRuleDestinationSummary' :: TopicRuleDestinationSummary -> Maybe HttpUrlDestinationSummary
$sel:createdAt:TopicRuleDestinationSummary' :: TopicRuleDestinationSummary -> Maybe POSIX
$sel:arn:TopicRuleDestinationSummary' :: TopicRuleDestinationSummary -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HttpUrlDestinationSummary
httpUrlSummary
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastUpdatedAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TopicRuleDestinationStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
statusReason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VpcDestinationSummary
vpcDestinationSummary

instance Prelude.NFData TopicRuleDestinationSummary where
  rnf :: TopicRuleDestinationSummary -> ()
rnf TopicRuleDestinationSummary' {Maybe Text
Maybe POSIX
Maybe HttpUrlDestinationSummary
Maybe TopicRuleDestinationStatus
Maybe VpcDestinationSummary
vpcDestinationSummary :: Maybe VpcDestinationSummary
statusReason :: Maybe Text
status :: Maybe TopicRuleDestinationStatus
lastUpdatedAt :: Maybe POSIX
httpUrlSummary :: Maybe HttpUrlDestinationSummary
createdAt :: Maybe POSIX
arn :: Maybe Text
$sel:vpcDestinationSummary:TopicRuleDestinationSummary' :: TopicRuleDestinationSummary -> Maybe VpcDestinationSummary
$sel:statusReason:TopicRuleDestinationSummary' :: TopicRuleDestinationSummary -> Maybe Text
$sel:status:TopicRuleDestinationSummary' :: TopicRuleDestinationSummary -> Maybe TopicRuleDestinationStatus
$sel:lastUpdatedAt:TopicRuleDestinationSummary' :: TopicRuleDestinationSummary -> Maybe POSIX
$sel:httpUrlSummary:TopicRuleDestinationSummary' :: TopicRuleDestinationSummary -> Maybe HttpUrlDestinationSummary
$sel:createdAt:TopicRuleDestinationSummary' :: TopicRuleDestinationSummary -> Maybe POSIX
$sel:arn:TopicRuleDestinationSummary' :: TopicRuleDestinationSummary -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HttpUrlDestinationSummary
httpUrlSummary
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastUpdatedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TopicRuleDestinationStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
statusReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe VpcDestinationSummary
vpcDestinationSummary