{-# 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.EC2.Types.TrafficMirrorTarget
-- 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.EC2.Types.TrafficMirrorTarget where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EC2.Internal
import Amazonka.EC2.Types.Tag
import Amazonka.EC2.Types.TrafficMirrorTargetType
import qualified Amazonka.Prelude as Prelude

-- | Describes a Traffic Mirror target.
--
-- /See:/ 'newTrafficMirrorTarget' smart constructor.
data TrafficMirrorTarget = TrafficMirrorTarget'
  { -- | Information about the Traffic Mirror target.
    TrafficMirrorTarget -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The ID of the Gateway Load Balancer endpoint.
    TrafficMirrorTarget -> Maybe Text
gatewayLoadBalancerEndpointId :: Prelude.Maybe Prelude.Text,
    -- | The network interface ID that is attached to the target.
    TrafficMirrorTarget -> Maybe Text
networkInterfaceId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the Network Load Balancer.
    TrafficMirrorTarget -> Maybe Text
networkLoadBalancerArn :: Prelude.Maybe Prelude.Text,
    -- | The ID of the account that owns the Traffic Mirror target.
    TrafficMirrorTarget -> Maybe Text
ownerId :: Prelude.Maybe Prelude.Text,
    -- | The tags assigned to the Traffic Mirror target.
    TrafficMirrorTarget -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The ID of the Traffic Mirror target.
    TrafficMirrorTarget -> Maybe Text
trafficMirrorTargetId :: Prelude.Maybe Prelude.Text,
    -- | The type of Traffic Mirror target.
    TrafficMirrorTarget -> Maybe TrafficMirrorTargetType
type' :: Prelude.Maybe TrafficMirrorTargetType
  }
  deriving (TrafficMirrorTarget -> TrafficMirrorTarget -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TrafficMirrorTarget -> TrafficMirrorTarget -> Bool
$c/= :: TrafficMirrorTarget -> TrafficMirrorTarget -> Bool
== :: TrafficMirrorTarget -> TrafficMirrorTarget -> Bool
$c== :: TrafficMirrorTarget -> TrafficMirrorTarget -> Bool
Prelude.Eq, ReadPrec [TrafficMirrorTarget]
ReadPrec TrafficMirrorTarget
Int -> ReadS TrafficMirrorTarget
ReadS [TrafficMirrorTarget]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TrafficMirrorTarget]
$creadListPrec :: ReadPrec [TrafficMirrorTarget]
readPrec :: ReadPrec TrafficMirrorTarget
$creadPrec :: ReadPrec TrafficMirrorTarget
readList :: ReadS [TrafficMirrorTarget]
$creadList :: ReadS [TrafficMirrorTarget]
readsPrec :: Int -> ReadS TrafficMirrorTarget
$creadsPrec :: Int -> ReadS TrafficMirrorTarget
Prelude.Read, Int -> TrafficMirrorTarget -> ShowS
[TrafficMirrorTarget] -> ShowS
TrafficMirrorTarget -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TrafficMirrorTarget] -> ShowS
$cshowList :: [TrafficMirrorTarget] -> ShowS
show :: TrafficMirrorTarget -> String
$cshow :: TrafficMirrorTarget -> String
showsPrec :: Int -> TrafficMirrorTarget -> ShowS
$cshowsPrec :: Int -> TrafficMirrorTarget -> ShowS
Prelude.Show, forall x. Rep TrafficMirrorTarget x -> TrafficMirrorTarget
forall x. TrafficMirrorTarget -> Rep TrafficMirrorTarget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TrafficMirrorTarget x -> TrafficMirrorTarget
$cfrom :: forall x. TrafficMirrorTarget -> Rep TrafficMirrorTarget x
Prelude.Generic)

-- |
-- Create a value of 'TrafficMirrorTarget' 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:
--
-- 'description', 'trafficMirrorTarget_description' - Information about the Traffic Mirror target.
--
-- 'gatewayLoadBalancerEndpointId', 'trafficMirrorTarget_gatewayLoadBalancerEndpointId' - The ID of the Gateway Load Balancer endpoint.
--
-- 'networkInterfaceId', 'trafficMirrorTarget_networkInterfaceId' - The network interface ID that is attached to the target.
--
-- 'networkLoadBalancerArn', 'trafficMirrorTarget_networkLoadBalancerArn' - The Amazon Resource Name (ARN) of the Network Load Balancer.
--
-- 'ownerId', 'trafficMirrorTarget_ownerId' - The ID of the account that owns the Traffic Mirror target.
--
-- 'tags', 'trafficMirrorTarget_tags' - The tags assigned to the Traffic Mirror target.
--
-- 'trafficMirrorTargetId', 'trafficMirrorTarget_trafficMirrorTargetId' - The ID of the Traffic Mirror target.
--
-- 'type'', 'trafficMirrorTarget_type' - The type of Traffic Mirror target.
newTrafficMirrorTarget ::
  TrafficMirrorTarget
newTrafficMirrorTarget :: TrafficMirrorTarget
newTrafficMirrorTarget =
  TrafficMirrorTarget'
    { $sel:description:TrafficMirrorTarget' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:gatewayLoadBalancerEndpointId:TrafficMirrorTarget' :: Maybe Text
gatewayLoadBalancerEndpointId = forall a. Maybe a
Prelude.Nothing,
      $sel:networkInterfaceId:TrafficMirrorTarget' :: Maybe Text
networkInterfaceId = forall a. Maybe a
Prelude.Nothing,
      $sel:networkLoadBalancerArn:TrafficMirrorTarget' :: Maybe Text
networkLoadBalancerArn = forall a. Maybe a
Prelude.Nothing,
      $sel:ownerId:TrafficMirrorTarget' :: Maybe Text
ownerId = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:TrafficMirrorTarget' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:trafficMirrorTargetId:TrafficMirrorTarget' :: Maybe Text
trafficMirrorTargetId = forall a. Maybe a
Prelude.Nothing,
      $sel:type':TrafficMirrorTarget' :: Maybe TrafficMirrorTargetType
type' = forall a. Maybe a
Prelude.Nothing
    }

-- | Information about the Traffic Mirror target.
trafficMirrorTarget_description :: Lens.Lens' TrafficMirrorTarget (Prelude.Maybe Prelude.Text)
trafficMirrorTarget_description :: Lens' TrafficMirrorTarget (Maybe Text)
trafficMirrorTarget_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrafficMirrorTarget' {Maybe Text
description :: Maybe Text
$sel:description:TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe Text
description} -> Maybe Text
description) (\s :: TrafficMirrorTarget
s@TrafficMirrorTarget' {} Maybe Text
a -> TrafficMirrorTarget
s {$sel:description:TrafficMirrorTarget' :: Maybe Text
description = Maybe Text
a} :: TrafficMirrorTarget)

-- | The ID of the Gateway Load Balancer endpoint.
trafficMirrorTarget_gatewayLoadBalancerEndpointId :: Lens.Lens' TrafficMirrorTarget (Prelude.Maybe Prelude.Text)
trafficMirrorTarget_gatewayLoadBalancerEndpointId :: Lens' TrafficMirrorTarget (Maybe Text)
trafficMirrorTarget_gatewayLoadBalancerEndpointId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrafficMirrorTarget' {Maybe Text
gatewayLoadBalancerEndpointId :: Maybe Text
$sel:gatewayLoadBalancerEndpointId:TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe Text
gatewayLoadBalancerEndpointId} -> Maybe Text
gatewayLoadBalancerEndpointId) (\s :: TrafficMirrorTarget
s@TrafficMirrorTarget' {} Maybe Text
a -> TrafficMirrorTarget
s {$sel:gatewayLoadBalancerEndpointId:TrafficMirrorTarget' :: Maybe Text
gatewayLoadBalancerEndpointId = Maybe Text
a} :: TrafficMirrorTarget)

-- | The network interface ID that is attached to the target.
trafficMirrorTarget_networkInterfaceId :: Lens.Lens' TrafficMirrorTarget (Prelude.Maybe Prelude.Text)
trafficMirrorTarget_networkInterfaceId :: Lens' TrafficMirrorTarget (Maybe Text)
trafficMirrorTarget_networkInterfaceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrafficMirrorTarget' {Maybe Text
networkInterfaceId :: Maybe Text
$sel:networkInterfaceId:TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe Text
networkInterfaceId} -> Maybe Text
networkInterfaceId) (\s :: TrafficMirrorTarget
s@TrafficMirrorTarget' {} Maybe Text
a -> TrafficMirrorTarget
s {$sel:networkInterfaceId:TrafficMirrorTarget' :: Maybe Text
networkInterfaceId = Maybe Text
a} :: TrafficMirrorTarget)

-- | The Amazon Resource Name (ARN) of the Network Load Balancer.
trafficMirrorTarget_networkLoadBalancerArn :: Lens.Lens' TrafficMirrorTarget (Prelude.Maybe Prelude.Text)
trafficMirrorTarget_networkLoadBalancerArn :: Lens' TrafficMirrorTarget (Maybe Text)
trafficMirrorTarget_networkLoadBalancerArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrafficMirrorTarget' {Maybe Text
networkLoadBalancerArn :: Maybe Text
$sel:networkLoadBalancerArn:TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe Text
networkLoadBalancerArn} -> Maybe Text
networkLoadBalancerArn) (\s :: TrafficMirrorTarget
s@TrafficMirrorTarget' {} Maybe Text
a -> TrafficMirrorTarget
s {$sel:networkLoadBalancerArn:TrafficMirrorTarget' :: Maybe Text
networkLoadBalancerArn = Maybe Text
a} :: TrafficMirrorTarget)

-- | The ID of the account that owns the Traffic Mirror target.
trafficMirrorTarget_ownerId :: Lens.Lens' TrafficMirrorTarget (Prelude.Maybe Prelude.Text)
trafficMirrorTarget_ownerId :: Lens' TrafficMirrorTarget (Maybe Text)
trafficMirrorTarget_ownerId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrafficMirrorTarget' {Maybe Text
ownerId :: Maybe Text
$sel:ownerId:TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe Text
ownerId} -> Maybe Text
ownerId) (\s :: TrafficMirrorTarget
s@TrafficMirrorTarget' {} Maybe Text
a -> TrafficMirrorTarget
s {$sel:ownerId:TrafficMirrorTarget' :: Maybe Text
ownerId = Maybe Text
a} :: TrafficMirrorTarget)

-- | The tags assigned to the Traffic Mirror target.
trafficMirrorTarget_tags :: Lens.Lens' TrafficMirrorTarget (Prelude.Maybe [Tag])
trafficMirrorTarget_tags :: Lens' TrafficMirrorTarget (Maybe [Tag])
trafficMirrorTarget_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrafficMirrorTarget' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: TrafficMirrorTarget
s@TrafficMirrorTarget' {} Maybe [Tag]
a -> TrafficMirrorTarget
s {$sel:tags:TrafficMirrorTarget' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: TrafficMirrorTarget) 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 ID of the Traffic Mirror target.
trafficMirrorTarget_trafficMirrorTargetId :: Lens.Lens' TrafficMirrorTarget (Prelude.Maybe Prelude.Text)
trafficMirrorTarget_trafficMirrorTargetId :: Lens' TrafficMirrorTarget (Maybe Text)
trafficMirrorTarget_trafficMirrorTargetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrafficMirrorTarget' {Maybe Text
trafficMirrorTargetId :: Maybe Text
$sel:trafficMirrorTargetId:TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe Text
trafficMirrorTargetId} -> Maybe Text
trafficMirrorTargetId) (\s :: TrafficMirrorTarget
s@TrafficMirrorTarget' {} Maybe Text
a -> TrafficMirrorTarget
s {$sel:trafficMirrorTargetId:TrafficMirrorTarget' :: Maybe Text
trafficMirrorTargetId = Maybe Text
a} :: TrafficMirrorTarget)

-- | The type of Traffic Mirror target.
trafficMirrorTarget_type :: Lens.Lens' TrafficMirrorTarget (Prelude.Maybe TrafficMirrorTargetType)
trafficMirrorTarget_type :: Lens' TrafficMirrorTarget (Maybe TrafficMirrorTargetType)
trafficMirrorTarget_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrafficMirrorTarget' {Maybe TrafficMirrorTargetType
type' :: Maybe TrafficMirrorTargetType
$sel:type':TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe TrafficMirrorTargetType
type'} -> Maybe TrafficMirrorTargetType
type') (\s :: TrafficMirrorTarget
s@TrafficMirrorTarget' {} Maybe TrafficMirrorTargetType
a -> TrafficMirrorTarget
s {$sel:type':TrafficMirrorTarget' :: Maybe TrafficMirrorTargetType
type' = Maybe TrafficMirrorTargetType
a} :: TrafficMirrorTarget)

instance Data.FromXML TrafficMirrorTarget where
  parseXML :: [Node] -> Either String TrafficMirrorTarget
parseXML [Node]
x =
    Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Tag]
-> Maybe Text
-> Maybe TrafficMirrorTargetType
-> TrafficMirrorTarget
TrafficMirrorTarget'
      forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"description")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"gatewayLoadBalancerEndpointId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"networkInterfaceId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"networkLoadBalancerArn")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ownerId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"tagSet"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"trafficMirrorTargetId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"type")

instance Prelude.Hashable TrafficMirrorTarget where
  hashWithSalt :: Int -> TrafficMirrorTarget -> Int
hashWithSalt Int
_salt TrafficMirrorTarget' {Maybe [Tag]
Maybe Text
Maybe TrafficMirrorTargetType
type' :: Maybe TrafficMirrorTargetType
trafficMirrorTargetId :: Maybe Text
tags :: Maybe [Tag]
ownerId :: Maybe Text
networkLoadBalancerArn :: Maybe Text
networkInterfaceId :: Maybe Text
gatewayLoadBalancerEndpointId :: Maybe Text
description :: Maybe Text
$sel:type':TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe TrafficMirrorTargetType
$sel:trafficMirrorTargetId:TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe Text
$sel:tags:TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe [Tag]
$sel:ownerId:TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe Text
$sel:networkLoadBalancerArn:TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe Text
$sel:networkInterfaceId:TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe Text
$sel:gatewayLoadBalancerEndpointId:TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe Text
$sel:description:TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
gatewayLoadBalancerEndpointId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
networkInterfaceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
networkLoadBalancerArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ownerId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
trafficMirrorTargetId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TrafficMirrorTargetType
type'

instance Prelude.NFData TrafficMirrorTarget where
  rnf :: TrafficMirrorTarget -> ()
rnf TrafficMirrorTarget' {Maybe [Tag]
Maybe Text
Maybe TrafficMirrorTargetType
type' :: Maybe TrafficMirrorTargetType
trafficMirrorTargetId :: Maybe Text
tags :: Maybe [Tag]
ownerId :: Maybe Text
networkLoadBalancerArn :: Maybe Text
networkInterfaceId :: Maybe Text
gatewayLoadBalancerEndpointId :: Maybe Text
description :: Maybe Text
$sel:type':TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe TrafficMirrorTargetType
$sel:trafficMirrorTargetId:TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe Text
$sel:tags:TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe [Tag]
$sel:ownerId:TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe Text
$sel:networkLoadBalancerArn:TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe Text
$sel:networkInterfaceId:TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe Text
$sel:gatewayLoadBalancerEndpointId:TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe Text
$sel:description:TrafficMirrorTarget' :: TrafficMirrorTarget -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
gatewayLoadBalancerEndpointId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
networkInterfaceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
networkLoadBalancerArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ownerId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
trafficMirrorTargetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TrafficMirrorTargetType
type'