{-# 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.TopicRuleDestination
-- 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.TopicRuleDestination 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.HttpUrlDestinationProperties
import Amazonka.IoT.Types.TopicRuleDestinationStatus
import Amazonka.IoT.Types.VpcDestinationProperties
import qualified Amazonka.Prelude as Prelude

-- | A topic rule destination.
--
-- /See:/ 'newTopicRuleDestination' smart constructor.
data TopicRuleDestination = TopicRuleDestination'
  { -- | The topic rule destination URL.
    TopicRuleDestination -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The date and time when the topic rule destination was created.
    TopicRuleDestination -> Maybe POSIX
createdAt :: Prelude.Maybe Data.POSIX,
    -- | Properties of the HTTP URL.
    TopicRuleDestination -> Maybe HttpUrlDestinationProperties
httpUrlProperties :: Prelude.Maybe HttpUrlDestinationProperties,
    -- | The date and time when the topic rule destination was last updated.
    TopicRuleDestination -> 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.
    TopicRuleDestination -> Maybe TopicRuleDestinationStatus
status :: Prelude.Maybe TopicRuleDestinationStatus,
    -- | Additional details or reason why the topic rule destination is in the
    -- current status.
    TopicRuleDestination -> Maybe Text
statusReason :: Prelude.Maybe Prelude.Text,
    -- | Properties of the virtual private cloud (VPC) connection.
    TopicRuleDestination -> Maybe VpcDestinationProperties
vpcProperties :: Prelude.Maybe VpcDestinationProperties
  }
  deriving (TopicRuleDestination -> TopicRuleDestination -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TopicRuleDestination -> TopicRuleDestination -> Bool
$c/= :: TopicRuleDestination -> TopicRuleDestination -> Bool
== :: TopicRuleDestination -> TopicRuleDestination -> Bool
$c== :: TopicRuleDestination -> TopicRuleDestination -> Bool
Prelude.Eq, ReadPrec [TopicRuleDestination]
ReadPrec TopicRuleDestination
Int -> ReadS TopicRuleDestination
ReadS [TopicRuleDestination]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TopicRuleDestination]
$creadListPrec :: ReadPrec [TopicRuleDestination]
readPrec :: ReadPrec TopicRuleDestination
$creadPrec :: ReadPrec TopicRuleDestination
readList :: ReadS [TopicRuleDestination]
$creadList :: ReadS [TopicRuleDestination]
readsPrec :: Int -> ReadS TopicRuleDestination
$creadsPrec :: Int -> ReadS TopicRuleDestination
Prelude.Read, Int -> TopicRuleDestination -> ShowS
[TopicRuleDestination] -> ShowS
TopicRuleDestination -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TopicRuleDestination] -> ShowS
$cshowList :: [TopicRuleDestination] -> ShowS
show :: TopicRuleDestination -> String
$cshow :: TopicRuleDestination -> String
showsPrec :: Int -> TopicRuleDestination -> ShowS
$cshowsPrec :: Int -> TopicRuleDestination -> ShowS
Prelude.Show, forall x. Rep TopicRuleDestination x -> TopicRuleDestination
forall x. TopicRuleDestination -> Rep TopicRuleDestination x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TopicRuleDestination x -> TopicRuleDestination
$cfrom :: forall x. TopicRuleDestination -> Rep TopicRuleDestination x
Prelude.Generic)

-- |
-- Create a value of 'TopicRuleDestination' 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', 'topicRuleDestination_arn' - The topic rule destination URL.
--
-- 'createdAt', 'topicRuleDestination_createdAt' - The date and time when the topic rule destination was created.
--
-- 'httpUrlProperties', 'topicRuleDestination_httpUrlProperties' - Properties of the HTTP URL.
--
-- 'lastUpdatedAt', 'topicRuleDestination_lastUpdatedAt' - The date and time when the topic rule destination was last updated.
--
-- 'status', 'topicRuleDestination_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', 'topicRuleDestination_statusReason' - Additional details or reason why the topic rule destination is in the
-- current status.
--
-- 'vpcProperties', 'topicRuleDestination_vpcProperties' - Properties of the virtual private cloud (VPC) connection.
newTopicRuleDestination ::
  TopicRuleDestination
newTopicRuleDestination :: TopicRuleDestination
newTopicRuleDestination =
  TopicRuleDestination'
    { $sel:arn:TopicRuleDestination' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:createdAt:TopicRuleDestination' :: Maybe POSIX
createdAt = forall a. Maybe a
Prelude.Nothing,
      $sel:httpUrlProperties:TopicRuleDestination' :: Maybe HttpUrlDestinationProperties
httpUrlProperties = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedAt:TopicRuleDestination' :: Maybe POSIX
lastUpdatedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:status:TopicRuleDestination' :: Maybe TopicRuleDestinationStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:statusReason:TopicRuleDestination' :: Maybe Text
statusReason = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcProperties:TopicRuleDestination' :: Maybe VpcDestinationProperties
vpcProperties = forall a. Maybe a
Prelude.Nothing
    }

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

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

-- | Properties of the HTTP URL.
topicRuleDestination_httpUrlProperties :: Lens.Lens' TopicRuleDestination (Prelude.Maybe HttpUrlDestinationProperties)
topicRuleDestination_httpUrlProperties :: Lens' TopicRuleDestination (Maybe HttpUrlDestinationProperties)
topicRuleDestination_httpUrlProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TopicRuleDestination' {Maybe HttpUrlDestinationProperties
httpUrlProperties :: Maybe HttpUrlDestinationProperties
$sel:httpUrlProperties:TopicRuleDestination' :: TopicRuleDestination -> Maybe HttpUrlDestinationProperties
httpUrlProperties} -> Maybe HttpUrlDestinationProperties
httpUrlProperties) (\s :: TopicRuleDestination
s@TopicRuleDestination' {} Maybe HttpUrlDestinationProperties
a -> TopicRuleDestination
s {$sel:httpUrlProperties:TopicRuleDestination' :: Maybe HttpUrlDestinationProperties
httpUrlProperties = Maybe HttpUrlDestinationProperties
a} :: TopicRuleDestination)

-- | The date and time when the topic rule destination was last updated.
topicRuleDestination_lastUpdatedAt :: Lens.Lens' TopicRuleDestination (Prelude.Maybe Prelude.UTCTime)
topicRuleDestination_lastUpdatedAt :: Lens' TopicRuleDestination (Maybe UTCTime)
topicRuleDestination_lastUpdatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TopicRuleDestination' {Maybe POSIX
lastUpdatedAt :: Maybe POSIX
$sel:lastUpdatedAt:TopicRuleDestination' :: TopicRuleDestination -> Maybe POSIX
lastUpdatedAt} -> Maybe POSIX
lastUpdatedAt) (\s :: TopicRuleDestination
s@TopicRuleDestination' {} Maybe POSIX
a -> TopicRuleDestination
s {$sel:lastUpdatedAt:TopicRuleDestination' :: Maybe POSIX
lastUpdatedAt = Maybe POSIX
a} :: TopicRuleDestination) 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.
topicRuleDestination_status :: Lens.Lens' TopicRuleDestination (Prelude.Maybe TopicRuleDestinationStatus)
topicRuleDestination_status :: Lens' TopicRuleDestination (Maybe TopicRuleDestinationStatus)
topicRuleDestination_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TopicRuleDestination' {Maybe TopicRuleDestinationStatus
status :: Maybe TopicRuleDestinationStatus
$sel:status:TopicRuleDestination' :: TopicRuleDestination -> Maybe TopicRuleDestinationStatus
status} -> Maybe TopicRuleDestinationStatus
status) (\s :: TopicRuleDestination
s@TopicRuleDestination' {} Maybe TopicRuleDestinationStatus
a -> TopicRuleDestination
s {$sel:status:TopicRuleDestination' :: Maybe TopicRuleDestinationStatus
status = Maybe TopicRuleDestinationStatus
a} :: TopicRuleDestination)

-- | Additional details or reason why the topic rule destination is in the
-- current status.
topicRuleDestination_statusReason :: Lens.Lens' TopicRuleDestination (Prelude.Maybe Prelude.Text)
topicRuleDestination_statusReason :: Lens' TopicRuleDestination (Maybe Text)
topicRuleDestination_statusReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TopicRuleDestination' {Maybe Text
statusReason :: Maybe Text
$sel:statusReason:TopicRuleDestination' :: TopicRuleDestination -> Maybe Text
statusReason} -> Maybe Text
statusReason) (\s :: TopicRuleDestination
s@TopicRuleDestination' {} Maybe Text
a -> TopicRuleDestination
s {$sel:statusReason:TopicRuleDestination' :: Maybe Text
statusReason = Maybe Text
a} :: TopicRuleDestination)

-- | Properties of the virtual private cloud (VPC) connection.
topicRuleDestination_vpcProperties :: Lens.Lens' TopicRuleDestination (Prelude.Maybe VpcDestinationProperties)
topicRuleDestination_vpcProperties :: Lens' TopicRuleDestination (Maybe VpcDestinationProperties)
topicRuleDestination_vpcProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TopicRuleDestination' {Maybe VpcDestinationProperties
vpcProperties :: Maybe VpcDestinationProperties
$sel:vpcProperties:TopicRuleDestination' :: TopicRuleDestination -> Maybe VpcDestinationProperties
vpcProperties} -> Maybe VpcDestinationProperties
vpcProperties) (\s :: TopicRuleDestination
s@TopicRuleDestination' {} Maybe VpcDestinationProperties
a -> TopicRuleDestination
s {$sel:vpcProperties:TopicRuleDestination' :: Maybe VpcDestinationProperties
vpcProperties = Maybe VpcDestinationProperties
a} :: TopicRuleDestination)

instance Data.FromJSON TopicRuleDestination where
  parseJSON :: Value -> Parser TopicRuleDestination
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"TopicRuleDestination"
      ( \Object
x ->
          Maybe Text
-> Maybe POSIX
-> Maybe HttpUrlDestinationProperties
-> Maybe POSIX
-> Maybe TopicRuleDestinationStatus
-> Maybe Text
-> Maybe VpcDestinationProperties
-> TopicRuleDestination
TopicRuleDestination'
            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
"httpUrlProperties")
            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
"vpcProperties")
      )

instance Prelude.Hashable TopicRuleDestination where
  hashWithSalt :: Int -> TopicRuleDestination -> Int
hashWithSalt Int
_salt TopicRuleDestination' {Maybe Text
Maybe POSIX
Maybe HttpUrlDestinationProperties
Maybe TopicRuleDestinationStatus
Maybe VpcDestinationProperties
vpcProperties :: Maybe VpcDestinationProperties
statusReason :: Maybe Text
status :: Maybe TopicRuleDestinationStatus
lastUpdatedAt :: Maybe POSIX
httpUrlProperties :: Maybe HttpUrlDestinationProperties
createdAt :: Maybe POSIX
arn :: Maybe Text
$sel:vpcProperties:TopicRuleDestination' :: TopicRuleDestination -> Maybe VpcDestinationProperties
$sel:statusReason:TopicRuleDestination' :: TopicRuleDestination -> Maybe Text
$sel:status:TopicRuleDestination' :: TopicRuleDestination -> Maybe TopicRuleDestinationStatus
$sel:lastUpdatedAt:TopicRuleDestination' :: TopicRuleDestination -> Maybe POSIX
$sel:httpUrlProperties:TopicRuleDestination' :: TopicRuleDestination -> Maybe HttpUrlDestinationProperties
$sel:createdAt:TopicRuleDestination' :: TopicRuleDestination -> Maybe POSIX
$sel:arn:TopicRuleDestination' :: TopicRuleDestination -> 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 HttpUrlDestinationProperties
httpUrlProperties
      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 VpcDestinationProperties
vpcProperties

instance Prelude.NFData TopicRuleDestination where
  rnf :: TopicRuleDestination -> ()
rnf TopicRuleDestination' {Maybe Text
Maybe POSIX
Maybe HttpUrlDestinationProperties
Maybe TopicRuleDestinationStatus
Maybe VpcDestinationProperties
vpcProperties :: Maybe VpcDestinationProperties
statusReason :: Maybe Text
status :: Maybe TopicRuleDestinationStatus
lastUpdatedAt :: Maybe POSIX
httpUrlProperties :: Maybe HttpUrlDestinationProperties
createdAt :: Maybe POSIX
arn :: Maybe Text
$sel:vpcProperties:TopicRuleDestination' :: TopicRuleDestination -> Maybe VpcDestinationProperties
$sel:statusReason:TopicRuleDestination' :: TopicRuleDestination -> Maybe Text
$sel:status:TopicRuleDestination' :: TopicRuleDestination -> Maybe TopicRuleDestinationStatus
$sel:lastUpdatedAt:TopicRuleDestination' :: TopicRuleDestination -> Maybe POSIX
$sel:httpUrlProperties:TopicRuleDestination' :: TopicRuleDestination -> Maybe HttpUrlDestinationProperties
$sel:createdAt:TopicRuleDestination' :: TopicRuleDestination -> Maybe POSIX
$sel:arn:TopicRuleDestination' :: TopicRuleDestination -> 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 HttpUrlDestinationProperties
httpUrlProperties
      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 VpcDestinationProperties
vpcProperties