{-# 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 #-}
module Amazonka.EC2.Types.Explanation 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.AnalysisAclRule
import Amazonka.EC2.Types.AnalysisComponent
import Amazonka.EC2.Types.AnalysisLoadBalancerListener
import Amazonka.EC2.Types.AnalysisLoadBalancerTarget
import Amazonka.EC2.Types.AnalysisRouteTableRoute
import Amazonka.EC2.Types.AnalysisSecurityGroupRule
import Amazonka.EC2.Types.PortRange
import Amazonka.EC2.Types.TransitGatewayRouteTableRoute
import qualified Amazonka.Prelude as Prelude
data Explanation = Explanation'
{
Explanation -> Maybe AnalysisComponent
acl :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe AnalysisAclRule
aclRule :: Prelude.Maybe AnalysisAclRule,
Explanation -> Maybe Text
address :: Prelude.Maybe Prelude.Text,
Explanation -> Maybe [Text]
addresses :: Prelude.Maybe [Prelude.Text],
Explanation -> Maybe AnalysisComponent
attachedTo :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe [Text]
availabilityZones :: Prelude.Maybe [Prelude.Text],
Explanation -> Maybe [Text]
cidrs :: Prelude.Maybe [Prelude.Text],
Explanation -> Maybe AnalysisLoadBalancerListener
classicLoadBalancerListener :: Prelude.Maybe AnalysisLoadBalancerListener,
Explanation -> Maybe AnalysisComponent
component :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe Text
componentAccount :: Prelude.Maybe Prelude.Text,
Explanation -> Maybe Text
componentRegion :: Prelude.Maybe Prelude.Text,
Explanation -> Maybe AnalysisComponent
customerGateway :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe AnalysisComponent
destination :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe AnalysisComponent
destinationVpc :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe Text
direction :: Prelude.Maybe Prelude.Text,
Explanation -> Maybe AnalysisComponent
elasticLoadBalancerListener :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe Text
explanationCode :: Prelude.Maybe Prelude.Text,
Explanation -> Maybe AnalysisComponent
ingressRouteTable :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe AnalysisComponent
internetGateway :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe Text
loadBalancerArn :: Prelude.Maybe Prelude.Text,
Explanation -> Maybe Natural
loadBalancerListenerPort :: Prelude.Maybe Prelude.Natural,
Explanation -> Maybe AnalysisLoadBalancerTarget
loadBalancerTarget :: Prelude.Maybe AnalysisLoadBalancerTarget,
Explanation -> Maybe AnalysisComponent
loadBalancerTargetGroup :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe [AnalysisComponent]
loadBalancerTargetGroups :: Prelude.Maybe [AnalysisComponent],
Explanation -> Maybe Natural
loadBalancerTargetPort :: Prelude.Maybe Prelude.Natural,
Explanation -> Maybe Text
missingComponent :: Prelude.Maybe Prelude.Text,
Explanation -> Maybe AnalysisComponent
natGateway :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe AnalysisComponent
networkInterface :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe Text
packetField :: Prelude.Maybe Prelude.Text,
Explanation -> Maybe Natural
port :: Prelude.Maybe Prelude.Natural,
Explanation -> Maybe [PortRange]
portRanges :: Prelude.Maybe [PortRange],
Explanation -> Maybe AnalysisComponent
prefixList :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe [Text]
protocols :: Prelude.Maybe [Prelude.Text],
Explanation -> Maybe AnalysisComponent
routeTable :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe AnalysisRouteTableRoute
routeTableRoute :: Prelude.Maybe AnalysisRouteTableRoute,
Explanation -> Maybe AnalysisComponent
securityGroup :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe AnalysisSecurityGroupRule
securityGroupRule :: Prelude.Maybe AnalysisSecurityGroupRule,
Explanation -> Maybe [AnalysisComponent]
securityGroups :: Prelude.Maybe [AnalysisComponent],
Explanation -> Maybe AnalysisComponent
sourceVpc :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe Text
state :: Prelude.Maybe Prelude.Text,
Explanation -> Maybe AnalysisComponent
subnet :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe AnalysisComponent
subnetRouteTable :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe AnalysisComponent
transitGateway :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe AnalysisComponent
transitGatewayAttachment :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe AnalysisComponent
transitGatewayRouteTable :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe TransitGatewayRouteTableRoute
transitGatewayRouteTableRoute :: Prelude.Maybe TransitGatewayRouteTableRoute,
Explanation -> Maybe AnalysisComponent
vpc :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe AnalysisComponent
vpcEndpoint :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe AnalysisComponent
vpcPeeringConnection :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe AnalysisComponent
vpnConnection :: Prelude.Maybe AnalysisComponent,
Explanation -> Maybe AnalysisComponent
vpnGateway :: Prelude.Maybe AnalysisComponent
}
deriving (Explanation -> Explanation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Explanation -> Explanation -> Bool
$c/= :: Explanation -> Explanation -> Bool
== :: Explanation -> Explanation -> Bool
$c== :: Explanation -> Explanation -> Bool
Prelude.Eq, ReadPrec [Explanation]
ReadPrec Explanation
Int -> ReadS Explanation
ReadS [Explanation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Explanation]
$creadListPrec :: ReadPrec [Explanation]
readPrec :: ReadPrec Explanation
$creadPrec :: ReadPrec Explanation
readList :: ReadS [Explanation]
$creadList :: ReadS [Explanation]
readsPrec :: Int -> ReadS Explanation
$creadsPrec :: Int -> ReadS Explanation
Prelude.Read, Int -> Explanation -> ShowS
[Explanation] -> ShowS
Explanation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Explanation] -> ShowS
$cshowList :: [Explanation] -> ShowS
show :: Explanation -> String
$cshow :: Explanation -> String
showsPrec :: Int -> Explanation -> ShowS
$cshowsPrec :: Int -> Explanation -> ShowS
Prelude.Show, forall x. Rep Explanation x -> Explanation
forall x. Explanation -> Rep Explanation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Explanation x -> Explanation
$cfrom :: forall x. Explanation -> Rep Explanation x
Prelude.Generic)
newExplanation ::
Explanation
newExplanation :: Explanation
newExplanation =
Explanation'
{ $sel:acl:Explanation' :: Maybe AnalysisComponent
acl = forall a. Maybe a
Prelude.Nothing,
$sel:aclRule:Explanation' :: Maybe AnalysisAclRule
aclRule = forall a. Maybe a
Prelude.Nothing,
$sel:address:Explanation' :: Maybe Text
address = forall a. Maybe a
Prelude.Nothing,
$sel:addresses:Explanation' :: Maybe [Text]
addresses = forall a. Maybe a
Prelude.Nothing,
$sel:attachedTo:Explanation' :: Maybe AnalysisComponent
attachedTo = forall a. Maybe a
Prelude.Nothing,
$sel:availabilityZones:Explanation' :: Maybe [Text]
availabilityZones = forall a. Maybe a
Prelude.Nothing,
$sel:cidrs:Explanation' :: Maybe [Text]
cidrs = forall a. Maybe a
Prelude.Nothing,
$sel:classicLoadBalancerListener:Explanation' :: Maybe AnalysisLoadBalancerListener
classicLoadBalancerListener = forall a. Maybe a
Prelude.Nothing,
$sel:component:Explanation' :: Maybe AnalysisComponent
component = forall a. Maybe a
Prelude.Nothing,
$sel:componentAccount:Explanation' :: Maybe Text
componentAccount = forall a. Maybe a
Prelude.Nothing,
$sel:componentRegion:Explanation' :: Maybe Text
componentRegion = forall a. Maybe a
Prelude.Nothing,
$sel:customerGateway:Explanation' :: Maybe AnalysisComponent
customerGateway = forall a. Maybe a
Prelude.Nothing,
$sel:destination:Explanation' :: Maybe AnalysisComponent
destination = forall a. Maybe a
Prelude.Nothing,
$sel:destinationVpc:Explanation' :: Maybe AnalysisComponent
destinationVpc = forall a. Maybe a
Prelude.Nothing,
$sel:direction:Explanation' :: Maybe Text
direction = forall a. Maybe a
Prelude.Nothing,
$sel:elasticLoadBalancerListener:Explanation' :: Maybe AnalysisComponent
elasticLoadBalancerListener = forall a. Maybe a
Prelude.Nothing,
$sel:explanationCode:Explanation' :: Maybe Text
explanationCode = forall a. Maybe a
Prelude.Nothing,
$sel:ingressRouteTable:Explanation' :: Maybe AnalysisComponent
ingressRouteTable = forall a. Maybe a
Prelude.Nothing,
$sel:internetGateway:Explanation' :: Maybe AnalysisComponent
internetGateway = forall a. Maybe a
Prelude.Nothing,
$sel:loadBalancerArn:Explanation' :: Maybe Text
loadBalancerArn = forall a. Maybe a
Prelude.Nothing,
$sel:loadBalancerListenerPort:Explanation' :: Maybe Natural
loadBalancerListenerPort = forall a. Maybe a
Prelude.Nothing,
$sel:loadBalancerTarget:Explanation' :: Maybe AnalysisLoadBalancerTarget
loadBalancerTarget = forall a. Maybe a
Prelude.Nothing,
$sel:loadBalancerTargetGroup:Explanation' :: Maybe AnalysisComponent
loadBalancerTargetGroup = forall a. Maybe a
Prelude.Nothing,
$sel:loadBalancerTargetGroups:Explanation' :: Maybe [AnalysisComponent]
loadBalancerTargetGroups = forall a. Maybe a
Prelude.Nothing,
$sel:loadBalancerTargetPort:Explanation' :: Maybe Natural
loadBalancerTargetPort = forall a. Maybe a
Prelude.Nothing,
$sel:missingComponent:Explanation' :: Maybe Text
missingComponent = forall a. Maybe a
Prelude.Nothing,
$sel:natGateway:Explanation' :: Maybe AnalysisComponent
natGateway = forall a. Maybe a
Prelude.Nothing,
$sel:networkInterface:Explanation' :: Maybe AnalysisComponent
networkInterface = forall a. Maybe a
Prelude.Nothing,
$sel:packetField:Explanation' :: Maybe Text
packetField = forall a. Maybe a
Prelude.Nothing,
$sel:port:Explanation' :: Maybe Natural
port = forall a. Maybe a
Prelude.Nothing,
$sel:portRanges:Explanation' :: Maybe [PortRange]
portRanges = forall a. Maybe a
Prelude.Nothing,
$sel:prefixList:Explanation' :: Maybe AnalysisComponent
prefixList = forall a. Maybe a
Prelude.Nothing,
$sel:protocols:Explanation' :: Maybe [Text]
protocols = forall a. Maybe a
Prelude.Nothing,
$sel:routeTable:Explanation' :: Maybe AnalysisComponent
routeTable = forall a. Maybe a
Prelude.Nothing,
$sel:routeTableRoute:Explanation' :: Maybe AnalysisRouteTableRoute
routeTableRoute = forall a. Maybe a
Prelude.Nothing,
$sel:securityGroup:Explanation' :: Maybe AnalysisComponent
securityGroup = forall a. Maybe a
Prelude.Nothing,
$sel:securityGroupRule:Explanation' :: Maybe AnalysisSecurityGroupRule
securityGroupRule = forall a. Maybe a
Prelude.Nothing,
$sel:securityGroups:Explanation' :: Maybe [AnalysisComponent]
securityGroups = forall a. Maybe a
Prelude.Nothing,
$sel:sourceVpc:Explanation' :: Maybe AnalysisComponent
sourceVpc = forall a. Maybe a
Prelude.Nothing,
$sel:state:Explanation' :: Maybe Text
state = forall a. Maybe a
Prelude.Nothing,
$sel:subnet:Explanation' :: Maybe AnalysisComponent
subnet = forall a. Maybe a
Prelude.Nothing,
$sel:subnetRouteTable:Explanation' :: Maybe AnalysisComponent
subnetRouteTable = forall a. Maybe a
Prelude.Nothing,
$sel:transitGateway:Explanation' :: Maybe AnalysisComponent
transitGateway = forall a. Maybe a
Prelude.Nothing,
$sel:transitGatewayAttachment:Explanation' :: Maybe AnalysisComponent
transitGatewayAttachment = forall a. Maybe a
Prelude.Nothing,
$sel:transitGatewayRouteTable:Explanation' :: Maybe AnalysisComponent
transitGatewayRouteTable = forall a. Maybe a
Prelude.Nothing,
$sel:transitGatewayRouteTableRoute:Explanation' :: Maybe TransitGatewayRouteTableRoute
transitGatewayRouteTableRoute = forall a. Maybe a
Prelude.Nothing,
$sel:vpc:Explanation' :: Maybe AnalysisComponent
vpc = forall a. Maybe a
Prelude.Nothing,
$sel:vpcEndpoint:Explanation' :: Maybe AnalysisComponent
vpcEndpoint = forall a. Maybe a
Prelude.Nothing,
$sel:vpcPeeringConnection:Explanation' :: Maybe AnalysisComponent
vpcPeeringConnection = forall a. Maybe a
Prelude.Nothing,
$sel:vpnConnection:Explanation' :: Maybe AnalysisComponent
vpnConnection = forall a. Maybe a
Prelude.Nothing,
$sel:vpnGateway:Explanation' :: Maybe AnalysisComponent
vpnGateway = forall a. Maybe a
Prelude.Nothing
}
explanation_acl :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_acl :: Lens' Explanation (Maybe AnalysisComponent)
explanation_acl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
acl :: Maybe AnalysisComponent
$sel:acl:Explanation' :: Explanation -> Maybe AnalysisComponent
acl} -> Maybe AnalysisComponent
acl) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:acl:Explanation' :: Maybe AnalysisComponent
acl = Maybe AnalysisComponent
a} :: Explanation)
explanation_aclRule :: Lens.Lens' Explanation (Prelude.Maybe AnalysisAclRule)
explanation_aclRule :: Lens' Explanation (Maybe AnalysisAclRule)
explanation_aclRule = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisAclRule
aclRule :: Maybe AnalysisAclRule
$sel:aclRule:Explanation' :: Explanation -> Maybe AnalysisAclRule
aclRule} -> Maybe AnalysisAclRule
aclRule) (\s :: Explanation
s@Explanation' {} Maybe AnalysisAclRule
a -> Explanation
s {$sel:aclRule:Explanation' :: Maybe AnalysisAclRule
aclRule = Maybe AnalysisAclRule
a} :: Explanation)
explanation_address :: Lens.Lens' Explanation (Prelude.Maybe Prelude.Text)
explanation_address :: Lens' Explanation (Maybe Text)
explanation_address = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe Text
address :: Maybe Text
$sel:address:Explanation' :: Explanation -> Maybe Text
address} -> Maybe Text
address) (\s :: Explanation
s@Explanation' {} Maybe Text
a -> Explanation
s {$sel:address:Explanation' :: Maybe Text
address = Maybe Text
a} :: Explanation)
explanation_addresses :: Lens.Lens' Explanation (Prelude.Maybe [Prelude.Text])
explanation_addresses :: Lens' Explanation (Maybe [Text])
explanation_addresses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe [Text]
addresses :: Maybe [Text]
$sel:addresses:Explanation' :: Explanation -> Maybe [Text]
addresses} -> Maybe [Text]
addresses) (\s :: Explanation
s@Explanation' {} Maybe [Text]
a -> Explanation
s {$sel:addresses:Explanation' :: Maybe [Text]
addresses = Maybe [Text]
a} :: Explanation) 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
explanation_attachedTo :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_attachedTo :: Lens' Explanation (Maybe AnalysisComponent)
explanation_attachedTo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
attachedTo :: Maybe AnalysisComponent
$sel:attachedTo:Explanation' :: Explanation -> Maybe AnalysisComponent
attachedTo} -> Maybe AnalysisComponent
attachedTo) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:attachedTo:Explanation' :: Maybe AnalysisComponent
attachedTo = Maybe AnalysisComponent
a} :: Explanation)
explanation_availabilityZones :: Lens.Lens' Explanation (Prelude.Maybe [Prelude.Text])
explanation_availabilityZones :: Lens' Explanation (Maybe [Text])
explanation_availabilityZones = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe [Text]
availabilityZones :: Maybe [Text]
$sel:availabilityZones:Explanation' :: Explanation -> Maybe [Text]
availabilityZones} -> Maybe [Text]
availabilityZones) (\s :: Explanation
s@Explanation' {} Maybe [Text]
a -> Explanation
s {$sel:availabilityZones:Explanation' :: Maybe [Text]
availabilityZones = Maybe [Text]
a} :: Explanation) 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
explanation_cidrs :: Lens.Lens' Explanation (Prelude.Maybe [Prelude.Text])
explanation_cidrs :: Lens' Explanation (Maybe [Text])
explanation_cidrs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe [Text]
cidrs :: Maybe [Text]
$sel:cidrs:Explanation' :: Explanation -> Maybe [Text]
cidrs} -> Maybe [Text]
cidrs) (\s :: Explanation
s@Explanation' {} Maybe [Text]
a -> Explanation
s {$sel:cidrs:Explanation' :: Maybe [Text]
cidrs = Maybe [Text]
a} :: Explanation) 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
explanation_classicLoadBalancerListener :: Lens.Lens' Explanation (Prelude.Maybe AnalysisLoadBalancerListener)
explanation_classicLoadBalancerListener :: Lens' Explanation (Maybe AnalysisLoadBalancerListener)
explanation_classicLoadBalancerListener = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisLoadBalancerListener
classicLoadBalancerListener :: Maybe AnalysisLoadBalancerListener
$sel:classicLoadBalancerListener:Explanation' :: Explanation -> Maybe AnalysisLoadBalancerListener
classicLoadBalancerListener} -> Maybe AnalysisLoadBalancerListener
classicLoadBalancerListener) (\s :: Explanation
s@Explanation' {} Maybe AnalysisLoadBalancerListener
a -> Explanation
s {$sel:classicLoadBalancerListener:Explanation' :: Maybe AnalysisLoadBalancerListener
classicLoadBalancerListener = Maybe AnalysisLoadBalancerListener
a} :: Explanation)
explanation_component :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_component :: Lens' Explanation (Maybe AnalysisComponent)
explanation_component = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
component :: Maybe AnalysisComponent
$sel:component:Explanation' :: Explanation -> Maybe AnalysisComponent
component} -> Maybe AnalysisComponent
component) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:component:Explanation' :: Maybe AnalysisComponent
component = Maybe AnalysisComponent
a} :: Explanation)
explanation_componentAccount :: Lens.Lens' Explanation (Prelude.Maybe Prelude.Text)
explanation_componentAccount :: Lens' Explanation (Maybe Text)
explanation_componentAccount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe Text
componentAccount :: Maybe Text
$sel:componentAccount:Explanation' :: Explanation -> Maybe Text
componentAccount} -> Maybe Text
componentAccount) (\s :: Explanation
s@Explanation' {} Maybe Text
a -> Explanation
s {$sel:componentAccount:Explanation' :: Maybe Text
componentAccount = Maybe Text
a} :: Explanation)
explanation_componentRegion :: Lens.Lens' Explanation (Prelude.Maybe Prelude.Text)
explanation_componentRegion :: Lens' Explanation (Maybe Text)
explanation_componentRegion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe Text
componentRegion :: Maybe Text
$sel:componentRegion:Explanation' :: Explanation -> Maybe Text
componentRegion} -> Maybe Text
componentRegion) (\s :: Explanation
s@Explanation' {} Maybe Text
a -> Explanation
s {$sel:componentRegion:Explanation' :: Maybe Text
componentRegion = Maybe Text
a} :: Explanation)
explanation_customerGateway :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_customerGateway :: Lens' Explanation (Maybe AnalysisComponent)
explanation_customerGateway = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
customerGateway :: Maybe AnalysisComponent
$sel:customerGateway:Explanation' :: Explanation -> Maybe AnalysisComponent
customerGateway} -> Maybe AnalysisComponent
customerGateway) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:customerGateway:Explanation' :: Maybe AnalysisComponent
customerGateway = Maybe AnalysisComponent
a} :: Explanation)
explanation_destination :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_destination :: Lens' Explanation (Maybe AnalysisComponent)
explanation_destination = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
destination :: Maybe AnalysisComponent
$sel:destination:Explanation' :: Explanation -> Maybe AnalysisComponent
destination} -> Maybe AnalysisComponent
destination) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:destination:Explanation' :: Maybe AnalysisComponent
destination = Maybe AnalysisComponent
a} :: Explanation)
explanation_destinationVpc :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_destinationVpc :: Lens' Explanation (Maybe AnalysisComponent)
explanation_destinationVpc = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
destinationVpc :: Maybe AnalysisComponent
$sel:destinationVpc:Explanation' :: Explanation -> Maybe AnalysisComponent
destinationVpc} -> Maybe AnalysisComponent
destinationVpc) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:destinationVpc:Explanation' :: Maybe AnalysisComponent
destinationVpc = Maybe AnalysisComponent
a} :: Explanation)
explanation_direction :: Lens.Lens' Explanation (Prelude.Maybe Prelude.Text)
explanation_direction :: Lens' Explanation (Maybe Text)
explanation_direction = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe Text
direction :: Maybe Text
$sel:direction:Explanation' :: Explanation -> Maybe Text
direction} -> Maybe Text
direction) (\s :: Explanation
s@Explanation' {} Maybe Text
a -> Explanation
s {$sel:direction:Explanation' :: Maybe Text
direction = Maybe Text
a} :: Explanation)
explanation_elasticLoadBalancerListener :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_elasticLoadBalancerListener :: Lens' Explanation (Maybe AnalysisComponent)
explanation_elasticLoadBalancerListener = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
elasticLoadBalancerListener :: Maybe AnalysisComponent
$sel:elasticLoadBalancerListener:Explanation' :: Explanation -> Maybe AnalysisComponent
elasticLoadBalancerListener} -> Maybe AnalysisComponent
elasticLoadBalancerListener) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:elasticLoadBalancerListener:Explanation' :: Maybe AnalysisComponent
elasticLoadBalancerListener = Maybe AnalysisComponent
a} :: Explanation)
explanation_explanationCode :: Lens.Lens' Explanation (Prelude.Maybe Prelude.Text)
explanation_explanationCode :: Lens' Explanation (Maybe Text)
explanation_explanationCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe Text
explanationCode :: Maybe Text
$sel:explanationCode:Explanation' :: Explanation -> Maybe Text
explanationCode} -> Maybe Text
explanationCode) (\s :: Explanation
s@Explanation' {} Maybe Text
a -> Explanation
s {$sel:explanationCode:Explanation' :: Maybe Text
explanationCode = Maybe Text
a} :: Explanation)
explanation_ingressRouteTable :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_ingressRouteTable :: Lens' Explanation (Maybe AnalysisComponent)
explanation_ingressRouteTable = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
ingressRouteTable :: Maybe AnalysisComponent
$sel:ingressRouteTable:Explanation' :: Explanation -> Maybe AnalysisComponent
ingressRouteTable} -> Maybe AnalysisComponent
ingressRouteTable) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:ingressRouteTable:Explanation' :: Maybe AnalysisComponent
ingressRouteTable = Maybe AnalysisComponent
a} :: Explanation)
explanation_internetGateway :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_internetGateway :: Lens' Explanation (Maybe AnalysisComponent)
explanation_internetGateway = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
internetGateway :: Maybe AnalysisComponent
$sel:internetGateway:Explanation' :: Explanation -> Maybe AnalysisComponent
internetGateway} -> Maybe AnalysisComponent
internetGateway) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:internetGateway:Explanation' :: Maybe AnalysisComponent
internetGateway = Maybe AnalysisComponent
a} :: Explanation)
explanation_loadBalancerArn :: Lens.Lens' Explanation (Prelude.Maybe Prelude.Text)
explanation_loadBalancerArn :: Lens' Explanation (Maybe Text)
explanation_loadBalancerArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe Text
loadBalancerArn :: Maybe Text
$sel:loadBalancerArn:Explanation' :: Explanation -> Maybe Text
loadBalancerArn} -> Maybe Text
loadBalancerArn) (\s :: Explanation
s@Explanation' {} Maybe Text
a -> Explanation
s {$sel:loadBalancerArn:Explanation' :: Maybe Text
loadBalancerArn = Maybe Text
a} :: Explanation)
explanation_loadBalancerListenerPort :: Lens.Lens' Explanation (Prelude.Maybe Prelude.Natural)
explanation_loadBalancerListenerPort :: Lens' Explanation (Maybe Natural)
explanation_loadBalancerListenerPort = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe Natural
loadBalancerListenerPort :: Maybe Natural
$sel:loadBalancerListenerPort:Explanation' :: Explanation -> Maybe Natural
loadBalancerListenerPort} -> Maybe Natural
loadBalancerListenerPort) (\s :: Explanation
s@Explanation' {} Maybe Natural
a -> Explanation
s {$sel:loadBalancerListenerPort:Explanation' :: Maybe Natural
loadBalancerListenerPort = Maybe Natural
a} :: Explanation)
explanation_loadBalancerTarget :: Lens.Lens' Explanation (Prelude.Maybe AnalysisLoadBalancerTarget)
explanation_loadBalancerTarget :: Lens' Explanation (Maybe AnalysisLoadBalancerTarget)
explanation_loadBalancerTarget = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisLoadBalancerTarget
loadBalancerTarget :: Maybe AnalysisLoadBalancerTarget
$sel:loadBalancerTarget:Explanation' :: Explanation -> Maybe AnalysisLoadBalancerTarget
loadBalancerTarget} -> Maybe AnalysisLoadBalancerTarget
loadBalancerTarget) (\s :: Explanation
s@Explanation' {} Maybe AnalysisLoadBalancerTarget
a -> Explanation
s {$sel:loadBalancerTarget:Explanation' :: Maybe AnalysisLoadBalancerTarget
loadBalancerTarget = Maybe AnalysisLoadBalancerTarget
a} :: Explanation)
explanation_loadBalancerTargetGroup :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_loadBalancerTargetGroup :: Lens' Explanation (Maybe AnalysisComponent)
explanation_loadBalancerTargetGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
loadBalancerTargetGroup :: Maybe AnalysisComponent
$sel:loadBalancerTargetGroup:Explanation' :: Explanation -> Maybe AnalysisComponent
loadBalancerTargetGroup} -> Maybe AnalysisComponent
loadBalancerTargetGroup) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:loadBalancerTargetGroup:Explanation' :: Maybe AnalysisComponent
loadBalancerTargetGroup = Maybe AnalysisComponent
a} :: Explanation)
explanation_loadBalancerTargetGroups :: Lens.Lens' Explanation (Prelude.Maybe [AnalysisComponent])
explanation_loadBalancerTargetGroups :: Lens' Explanation (Maybe [AnalysisComponent])
explanation_loadBalancerTargetGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe [AnalysisComponent]
loadBalancerTargetGroups :: Maybe [AnalysisComponent]
$sel:loadBalancerTargetGroups:Explanation' :: Explanation -> Maybe [AnalysisComponent]
loadBalancerTargetGroups} -> Maybe [AnalysisComponent]
loadBalancerTargetGroups) (\s :: Explanation
s@Explanation' {} Maybe [AnalysisComponent]
a -> Explanation
s {$sel:loadBalancerTargetGroups:Explanation' :: Maybe [AnalysisComponent]
loadBalancerTargetGroups = Maybe [AnalysisComponent]
a} :: Explanation) 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
explanation_loadBalancerTargetPort :: Lens.Lens' Explanation (Prelude.Maybe Prelude.Natural)
explanation_loadBalancerTargetPort :: Lens' Explanation (Maybe Natural)
explanation_loadBalancerTargetPort = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe Natural
loadBalancerTargetPort :: Maybe Natural
$sel:loadBalancerTargetPort:Explanation' :: Explanation -> Maybe Natural
loadBalancerTargetPort} -> Maybe Natural
loadBalancerTargetPort) (\s :: Explanation
s@Explanation' {} Maybe Natural
a -> Explanation
s {$sel:loadBalancerTargetPort:Explanation' :: Maybe Natural
loadBalancerTargetPort = Maybe Natural
a} :: Explanation)
explanation_missingComponent :: Lens.Lens' Explanation (Prelude.Maybe Prelude.Text)
explanation_missingComponent :: Lens' Explanation (Maybe Text)
explanation_missingComponent = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe Text
missingComponent :: Maybe Text
$sel:missingComponent:Explanation' :: Explanation -> Maybe Text
missingComponent} -> Maybe Text
missingComponent) (\s :: Explanation
s@Explanation' {} Maybe Text
a -> Explanation
s {$sel:missingComponent:Explanation' :: Maybe Text
missingComponent = Maybe Text
a} :: Explanation)
explanation_natGateway :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_natGateway :: Lens' Explanation (Maybe AnalysisComponent)
explanation_natGateway = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
natGateway :: Maybe AnalysisComponent
$sel:natGateway:Explanation' :: Explanation -> Maybe AnalysisComponent
natGateway} -> Maybe AnalysisComponent
natGateway) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:natGateway:Explanation' :: Maybe AnalysisComponent
natGateway = Maybe AnalysisComponent
a} :: Explanation)
explanation_networkInterface :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_networkInterface :: Lens' Explanation (Maybe AnalysisComponent)
explanation_networkInterface = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
networkInterface :: Maybe AnalysisComponent
$sel:networkInterface:Explanation' :: Explanation -> Maybe AnalysisComponent
networkInterface} -> Maybe AnalysisComponent
networkInterface) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:networkInterface:Explanation' :: Maybe AnalysisComponent
networkInterface = Maybe AnalysisComponent
a} :: Explanation)
explanation_packetField :: Lens.Lens' Explanation (Prelude.Maybe Prelude.Text)
explanation_packetField :: Lens' Explanation (Maybe Text)
explanation_packetField = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe Text
packetField :: Maybe Text
$sel:packetField:Explanation' :: Explanation -> Maybe Text
packetField} -> Maybe Text
packetField) (\s :: Explanation
s@Explanation' {} Maybe Text
a -> Explanation
s {$sel:packetField:Explanation' :: Maybe Text
packetField = Maybe Text
a} :: Explanation)
explanation_port :: Lens.Lens' Explanation (Prelude.Maybe Prelude.Natural)
explanation_port :: Lens' Explanation (Maybe Natural)
explanation_port = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe Natural
port :: Maybe Natural
$sel:port:Explanation' :: Explanation -> Maybe Natural
port} -> Maybe Natural
port) (\s :: Explanation
s@Explanation' {} Maybe Natural
a -> Explanation
s {$sel:port:Explanation' :: Maybe Natural
port = Maybe Natural
a} :: Explanation)
explanation_portRanges :: Lens.Lens' Explanation (Prelude.Maybe [PortRange])
explanation_portRanges :: Lens' Explanation (Maybe [PortRange])
explanation_portRanges = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe [PortRange]
portRanges :: Maybe [PortRange]
$sel:portRanges:Explanation' :: Explanation -> Maybe [PortRange]
portRanges} -> Maybe [PortRange]
portRanges) (\s :: Explanation
s@Explanation' {} Maybe [PortRange]
a -> Explanation
s {$sel:portRanges:Explanation' :: Maybe [PortRange]
portRanges = Maybe [PortRange]
a} :: Explanation) 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
explanation_prefixList :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_prefixList :: Lens' Explanation (Maybe AnalysisComponent)
explanation_prefixList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
prefixList :: Maybe AnalysisComponent
$sel:prefixList:Explanation' :: Explanation -> Maybe AnalysisComponent
prefixList} -> Maybe AnalysisComponent
prefixList) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:prefixList:Explanation' :: Maybe AnalysisComponent
prefixList = Maybe AnalysisComponent
a} :: Explanation)
explanation_protocols :: Lens.Lens' Explanation (Prelude.Maybe [Prelude.Text])
explanation_protocols :: Lens' Explanation (Maybe [Text])
explanation_protocols = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe [Text]
protocols :: Maybe [Text]
$sel:protocols:Explanation' :: Explanation -> Maybe [Text]
protocols} -> Maybe [Text]
protocols) (\s :: Explanation
s@Explanation' {} Maybe [Text]
a -> Explanation
s {$sel:protocols:Explanation' :: Maybe [Text]
protocols = Maybe [Text]
a} :: Explanation) 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
explanation_routeTable :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_routeTable :: Lens' Explanation (Maybe AnalysisComponent)
explanation_routeTable = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
routeTable :: Maybe AnalysisComponent
$sel:routeTable:Explanation' :: Explanation -> Maybe AnalysisComponent
routeTable} -> Maybe AnalysisComponent
routeTable) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:routeTable:Explanation' :: Maybe AnalysisComponent
routeTable = Maybe AnalysisComponent
a} :: Explanation)
explanation_routeTableRoute :: Lens.Lens' Explanation (Prelude.Maybe AnalysisRouteTableRoute)
explanation_routeTableRoute :: Lens' Explanation (Maybe AnalysisRouteTableRoute)
explanation_routeTableRoute = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisRouteTableRoute
routeTableRoute :: Maybe AnalysisRouteTableRoute
$sel:routeTableRoute:Explanation' :: Explanation -> Maybe AnalysisRouteTableRoute
routeTableRoute} -> Maybe AnalysisRouteTableRoute
routeTableRoute) (\s :: Explanation
s@Explanation' {} Maybe AnalysisRouteTableRoute
a -> Explanation
s {$sel:routeTableRoute:Explanation' :: Maybe AnalysisRouteTableRoute
routeTableRoute = Maybe AnalysisRouteTableRoute
a} :: Explanation)
explanation_securityGroup :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_securityGroup :: Lens' Explanation (Maybe AnalysisComponent)
explanation_securityGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
securityGroup :: Maybe AnalysisComponent
$sel:securityGroup:Explanation' :: Explanation -> Maybe AnalysisComponent
securityGroup} -> Maybe AnalysisComponent
securityGroup) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:securityGroup:Explanation' :: Maybe AnalysisComponent
securityGroup = Maybe AnalysisComponent
a} :: Explanation)
explanation_securityGroupRule :: Lens.Lens' Explanation (Prelude.Maybe AnalysisSecurityGroupRule)
explanation_securityGroupRule :: Lens' Explanation (Maybe AnalysisSecurityGroupRule)
explanation_securityGroupRule = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisSecurityGroupRule
securityGroupRule :: Maybe AnalysisSecurityGroupRule
$sel:securityGroupRule:Explanation' :: Explanation -> Maybe AnalysisSecurityGroupRule
securityGroupRule} -> Maybe AnalysisSecurityGroupRule
securityGroupRule) (\s :: Explanation
s@Explanation' {} Maybe AnalysisSecurityGroupRule
a -> Explanation
s {$sel:securityGroupRule:Explanation' :: Maybe AnalysisSecurityGroupRule
securityGroupRule = Maybe AnalysisSecurityGroupRule
a} :: Explanation)
explanation_securityGroups :: Lens.Lens' Explanation (Prelude.Maybe [AnalysisComponent])
explanation_securityGroups :: Lens' Explanation (Maybe [AnalysisComponent])
explanation_securityGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe [AnalysisComponent]
securityGroups :: Maybe [AnalysisComponent]
$sel:securityGroups:Explanation' :: Explanation -> Maybe [AnalysisComponent]
securityGroups} -> Maybe [AnalysisComponent]
securityGroups) (\s :: Explanation
s@Explanation' {} Maybe [AnalysisComponent]
a -> Explanation
s {$sel:securityGroups:Explanation' :: Maybe [AnalysisComponent]
securityGroups = Maybe [AnalysisComponent]
a} :: Explanation) 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
explanation_sourceVpc :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_sourceVpc :: Lens' Explanation (Maybe AnalysisComponent)
explanation_sourceVpc = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
sourceVpc :: Maybe AnalysisComponent
$sel:sourceVpc:Explanation' :: Explanation -> Maybe AnalysisComponent
sourceVpc} -> Maybe AnalysisComponent
sourceVpc) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:sourceVpc:Explanation' :: Maybe AnalysisComponent
sourceVpc = Maybe AnalysisComponent
a} :: Explanation)
explanation_state :: Lens.Lens' Explanation (Prelude.Maybe Prelude.Text)
explanation_state :: Lens' Explanation (Maybe Text)
explanation_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe Text
state :: Maybe Text
$sel:state:Explanation' :: Explanation -> Maybe Text
state} -> Maybe Text
state) (\s :: Explanation
s@Explanation' {} Maybe Text
a -> Explanation
s {$sel:state:Explanation' :: Maybe Text
state = Maybe Text
a} :: Explanation)
explanation_subnet :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_subnet :: Lens' Explanation (Maybe AnalysisComponent)
explanation_subnet = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
subnet :: Maybe AnalysisComponent
$sel:subnet:Explanation' :: Explanation -> Maybe AnalysisComponent
subnet} -> Maybe AnalysisComponent
subnet) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:subnet:Explanation' :: Maybe AnalysisComponent
subnet = Maybe AnalysisComponent
a} :: Explanation)
explanation_subnetRouteTable :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_subnetRouteTable :: Lens' Explanation (Maybe AnalysisComponent)
explanation_subnetRouteTable = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
subnetRouteTable :: Maybe AnalysisComponent
$sel:subnetRouteTable:Explanation' :: Explanation -> Maybe AnalysisComponent
subnetRouteTable} -> Maybe AnalysisComponent
subnetRouteTable) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:subnetRouteTable:Explanation' :: Maybe AnalysisComponent
subnetRouteTable = Maybe AnalysisComponent
a} :: Explanation)
explanation_transitGateway :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_transitGateway :: Lens' Explanation (Maybe AnalysisComponent)
explanation_transitGateway = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
transitGateway :: Maybe AnalysisComponent
$sel:transitGateway:Explanation' :: Explanation -> Maybe AnalysisComponent
transitGateway} -> Maybe AnalysisComponent
transitGateway) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:transitGateway:Explanation' :: Maybe AnalysisComponent
transitGateway = Maybe AnalysisComponent
a} :: Explanation)
explanation_transitGatewayAttachment :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_transitGatewayAttachment :: Lens' Explanation (Maybe AnalysisComponent)
explanation_transitGatewayAttachment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
transitGatewayAttachment :: Maybe AnalysisComponent
$sel:transitGatewayAttachment:Explanation' :: Explanation -> Maybe AnalysisComponent
transitGatewayAttachment} -> Maybe AnalysisComponent
transitGatewayAttachment) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:transitGatewayAttachment:Explanation' :: Maybe AnalysisComponent
transitGatewayAttachment = Maybe AnalysisComponent
a} :: Explanation)
explanation_transitGatewayRouteTable :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_transitGatewayRouteTable :: Lens' Explanation (Maybe AnalysisComponent)
explanation_transitGatewayRouteTable = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
transitGatewayRouteTable :: Maybe AnalysisComponent
$sel:transitGatewayRouteTable:Explanation' :: Explanation -> Maybe AnalysisComponent
transitGatewayRouteTable} -> Maybe AnalysisComponent
transitGatewayRouteTable) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:transitGatewayRouteTable:Explanation' :: Maybe AnalysisComponent
transitGatewayRouteTable = Maybe AnalysisComponent
a} :: Explanation)
explanation_transitGatewayRouteTableRoute :: Lens.Lens' Explanation (Prelude.Maybe TransitGatewayRouteTableRoute)
explanation_transitGatewayRouteTableRoute :: Lens' Explanation (Maybe TransitGatewayRouteTableRoute)
explanation_transitGatewayRouteTableRoute = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe TransitGatewayRouteTableRoute
transitGatewayRouteTableRoute :: Maybe TransitGatewayRouteTableRoute
$sel:transitGatewayRouteTableRoute:Explanation' :: Explanation -> Maybe TransitGatewayRouteTableRoute
transitGatewayRouteTableRoute} -> Maybe TransitGatewayRouteTableRoute
transitGatewayRouteTableRoute) (\s :: Explanation
s@Explanation' {} Maybe TransitGatewayRouteTableRoute
a -> Explanation
s {$sel:transitGatewayRouteTableRoute:Explanation' :: Maybe TransitGatewayRouteTableRoute
transitGatewayRouteTableRoute = Maybe TransitGatewayRouteTableRoute
a} :: Explanation)
explanation_vpc :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_vpc :: Lens' Explanation (Maybe AnalysisComponent)
explanation_vpc = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
vpc :: Maybe AnalysisComponent
$sel:vpc:Explanation' :: Explanation -> Maybe AnalysisComponent
vpc} -> Maybe AnalysisComponent
vpc) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:vpc:Explanation' :: Maybe AnalysisComponent
vpc = Maybe AnalysisComponent
a} :: Explanation)
explanation_vpcEndpoint :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_vpcEndpoint :: Lens' Explanation (Maybe AnalysisComponent)
explanation_vpcEndpoint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
vpcEndpoint :: Maybe AnalysisComponent
$sel:vpcEndpoint:Explanation' :: Explanation -> Maybe AnalysisComponent
vpcEndpoint} -> Maybe AnalysisComponent
vpcEndpoint) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:vpcEndpoint:Explanation' :: Maybe AnalysisComponent
vpcEndpoint = Maybe AnalysisComponent
a} :: Explanation)
explanation_vpcPeeringConnection :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_vpcPeeringConnection :: Lens' Explanation (Maybe AnalysisComponent)
explanation_vpcPeeringConnection = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
vpcPeeringConnection :: Maybe AnalysisComponent
$sel:vpcPeeringConnection:Explanation' :: Explanation -> Maybe AnalysisComponent
vpcPeeringConnection} -> Maybe AnalysisComponent
vpcPeeringConnection) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:vpcPeeringConnection:Explanation' :: Maybe AnalysisComponent
vpcPeeringConnection = Maybe AnalysisComponent
a} :: Explanation)
explanation_vpnConnection :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_vpnConnection :: Lens' Explanation (Maybe AnalysisComponent)
explanation_vpnConnection = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
vpnConnection :: Maybe AnalysisComponent
$sel:vpnConnection:Explanation' :: Explanation -> Maybe AnalysisComponent
vpnConnection} -> Maybe AnalysisComponent
vpnConnection) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:vpnConnection:Explanation' :: Maybe AnalysisComponent
vpnConnection = Maybe AnalysisComponent
a} :: Explanation)
explanation_vpnGateway :: Lens.Lens' Explanation (Prelude.Maybe AnalysisComponent)
explanation_vpnGateway :: Lens' Explanation (Maybe AnalysisComponent)
explanation_vpnGateway = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Explanation' {Maybe AnalysisComponent
vpnGateway :: Maybe AnalysisComponent
$sel:vpnGateway:Explanation' :: Explanation -> Maybe AnalysisComponent
vpnGateway} -> Maybe AnalysisComponent
vpnGateway) (\s :: Explanation
s@Explanation' {} Maybe AnalysisComponent
a -> Explanation
s {$sel:vpnGateway:Explanation' :: Maybe AnalysisComponent
vpnGateway = Maybe AnalysisComponent
a} :: Explanation)
instance Data.FromXML Explanation where
parseXML :: [Node] -> Either String Explanation
parseXML [Node]
x =
Maybe AnalysisComponent
-> Maybe AnalysisAclRule
-> Maybe Text
-> Maybe [Text]
-> Maybe AnalysisComponent
-> Maybe [Text]
-> Maybe [Text]
-> Maybe AnalysisLoadBalancerListener
-> Maybe AnalysisComponent
-> Maybe Text
-> Maybe Text
-> Maybe AnalysisComponent
-> Maybe AnalysisComponent
-> Maybe AnalysisComponent
-> Maybe Text
-> Maybe AnalysisComponent
-> Maybe Text
-> Maybe AnalysisComponent
-> Maybe AnalysisComponent
-> Maybe Text
-> Maybe Natural
-> Maybe AnalysisLoadBalancerTarget
-> Maybe AnalysisComponent
-> Maybe [AnalysisComponent]
-> Maybe Natural
-> Maybe Text
-> Maybe AnalysisComponent
-> Maybe AnalysisComponent
-> Maybe Text
-> Maybe Natural
-> Maybe [PortRange]
-> Maybe AnalysisComponent
-> Maybe [Text]
-> Maybe AnalysisComponent
-> Maybe AnalysisRouteTableRoute
-> Maybe AnalysisComponent
-> Maybe AnalysisSecurityGroupRule
-> Maybe [AnalysisComponent]
-> Maybe AnalysisComponent
-> Maybe Text
-> Maybe AnalysisComponent
-> Maybe AnalysisComponent
-> Maybe AnalysisComponent
-> Maybe AnalysisComponent
-> Maybe AnalysisComponent
-> Maybe TransitGatewayRouteTableRoute
-> Maybe AnalysisComponent
-> Maybe AnalysisComponent
-> Maybe AnalysisComponent
-> Maybe AnalysisComponent
-> Maybe AnalysisComponent
-> Explanation
Explanation'
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
"acl")
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
"aclRule")
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
"address")
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
"addressSet"
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
"attachedTo")
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
"availabilityZoneSet"
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
"cidrSet"
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
"classicLoadBalancerListener")
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
"component")
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
"componentAccount")
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
"componentRegion")
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
"customerGateway")
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
"destination")
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
"destinationVpc")
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
"direction")
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
"elasticLoadBalancerListener")
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
"explanationCode")
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
"ingressRouteTable")
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
"internetGateway")
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
"loadBalancerArn")
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
"loadBalancerListenerPort")
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
"loadBalancerTarget")
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
"loadBalancerTargetGroup")
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
"loadBalancerTargetGroupSet"
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
"loadBalancerTargetPort")
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
"missingComponent")
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
"natGateway")
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
"networkInterface")
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
"packetField")
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
"port")
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
"portRangeSet"
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
"prefixList")
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
"protocolSet"
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
"routeTable")
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
"routeTableRoute")
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
"securityGroup")
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
"securityGroupRule")
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
"securityGroupSet"
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
"sourceVpc")
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
"state")
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
"subnet")
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
"subnetRouteTable")
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
"transitGateway")
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
"transitGatewayAttachment")
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
"transitGatewayRouteTable")
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
"transitGatewayRouteTableRoute")
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
"vpc")
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
"vpcEndpoint")
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
"vpcPeeringConnection")
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
"vpnConnection")
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
"vpnGateway")
instance Prelude.Hashable Explanation where
hashWithSalt :: Int -> Explanation -> Int
hashWithSalt Int
_salt Explanation' {Maybe Natural
Maybe [Text]
Maybe [AnalysisComponent]
Maybe [PortRange]
Maybe Text
Maybe AnalysisComponent
Maybe AnalysisLoadBalancerListener
Maybe AnalysisLoadBalancerTarget
Maybe AnalysisRouteTableRoute
Maybe AnalysisSecurityGroupRule
Maybe AnalysisAclRule
Maybe TransitGatewayRouteTableRoute
vpnGateway :: Maybe AnalysisComponent
vpnConnection :: Maybe AnalysisComponent
vpcPeeringConnection :: Maybe AnalysisComponent
vpcEndpoint :: Maybe AnalysisComponent
vpc :: Maybe AnalysisComponent
transitGatewayRouteTableRoute :: Maybe TransitGatewayRouteTableRoute
transitGatewayRouteTable :: Maybe AnalysisComponent
transitGatewayAttachment :: Maybe AnalysisComponent
transitGateway :: Maybe AnalysisComponent
subnetRouteTable :: Maybe AnalysisComponent
subnet :: Maybe AnalysisComponent
state :: Maybe Text
sourceVpc :: Maybe AnalysisComponent
securityGroups :: Maybe [AnalysisComponent]
securityGroupRule :: Maybe AnalysisSecurityGroupRule
securityGroup :: Maybe AnalysisComponent
routeTableRoute :: Maybe AnalysisRouteTableRoute
routeTable :: Maybe AnalysisComponent
protocols :: Maybe [Text]
prefixList :: Maybe AnalysisComponent
portRanges :: Maybe [PortRange]
port :: Maybe Natural
packetField :: Maybe Text
networkInterface :: Maybe AnalysisComponent
natGateway :: Maybe AnalysisComponent
missingComponent :: Maybe Text
loadBalancerTargetPort :: Maybe Natural
loadBalancerTargetGroups :: Maybe [AnalysisComponent]
loadBalancerTargetGroup :: Maybe AnalysisComponent
loadBalancerTarget :: Maybe AnalysisLoadBalancerTarget
loadBalancerListenerPort :: Maybe Natural
loadBalancerArn :: Maybe Text
internetGateway :: Maybe AnalysisComponent
ingressRouteTable :: Maybe AnalysisComponent
explanationCode :: Maybe Text
elasticLoadBalancerListener :: Maybe AnalysisComponent
direction :: Maybe Text
destinationVpc :: Maybe AnalysisComponent
destination :: Maybe AnalysisComponent
customerGateway :: Maybe AnalysisComponent
componentRegion :: Maybe Text
componentAccount :: Maybe Text
component :: Maybe AnalysisComponent
classicLoadBalancerListener :: Maybe AnalysisLoadBalancerListener
cidrs :: Maybe [Text]
availabilityZones :: Maybe [Text]
attachedTo :: Maybe AnalysisComponent
addresses :: Maybe [Text]
address :: Maybe Text
aclRule :: Maybe AnalysisAclRule
acl :: Maybe AnalysisComponent
$sel:vpnGateway:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:vpnConnection:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:vpcPeeringConnection:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:vpcEndpoint:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:vpc:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:transitGatewayRouteTableRoute:Explanation' :: Explanation -> Maybe TransitGatewayRouteTableRoute
$sel:transitGatewayRouteTable:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:transitGatewayAttachment:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:transitGateway:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:subnetRouteTable:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:subnet:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:state:Explanation' :: Explanation -> Maybe Text
$sel:sourceVpc:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:securityGroups:Explanation' :: Explanation -> Maybe [AnalysisComponent]
$sel:securityGroupRule:Explanation' :: Explanation -> Maybe AnalysisSecurityGroupRule
$sel:securityGroup:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:routeTableRoute:Explanation' :: Explanation -> Maybe AnalysisRouteTableRoute
$sel:routeTable:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:protocols:Explanation' :: Explanation -> Maybe [Text]
$sel:prefixList:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:portRanges:Explanation' :: Explanation -> Maybe [PortRange]
$sel:port:Explanation' :: Explanation -> Maybe Natural
$sel:packetField:Explanation' :: Explanation -> Maybe Text
$sel:networkInterface:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:natGateway:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:missingComponent:Explanation' :: Explanation -> Maybe Text
$sel:loadBalancerTargetPort:Explanation' :: Explanation -> Maybe Natural
$sel:loadBalancerTargetGroups:Explanation' :: Explanation -> Maybe [AnalysisComponent]
$sel:loadBalancerTargetGroup:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:loadBalancerTarget:Explanation' :: Explanation -> Maybe AnalysisLoadBalancerTarget
$sel:loadBalancerListenerPort:Explanation' :: Explanation -> Maybe Natural
$sel:loadBalancerArn:Explanation' :: Explanation -> Maybe Text
$sel:internetGateway:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:ingressRouteTable:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:explanationCode:Explanation' :: Explanation -> Maybe Text
$sel:elasticLoadBalancerListener:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:direction:Explanation' :: Explanation -> Maybe Text
$sel:destinationVpc:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:destination:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:customerGateway:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:componentRegion:Explanation' :: Explanation -> Maybe Text
$sel:componentAccount:Explanation' :: Explanation -> Maybe Text
$sel:component:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:classicLoadBalancerListener:Explanation' :: Explanation -> Maybe AnalysisLoadBalancerListener
$sel:cidrs:Explanation' :: Explanation -> Maybe [Text]
$sel:availabilityZones:Explanation' :: Explanation -> Maybe [Text]
$sel:attachedTo:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:addresses:Explanation' :: Explanation -> Maybe [Text]
$sel:address:Explanation' :: Explanation -> Maybe Text
$sel:aclRule:Explanation' :: Explanation -> Maybe AnalysisAclRule
$sel:acl:Explanation' :: Explanation -> Maybe AnalysisComponent
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
acl
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisAclRule
aclRule
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
address
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
addresses
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
attachedTo
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
availabilityZones
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
cidrs
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisLoadBalancerListener
classicLoadBalancerListener
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
component
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
componentAccount
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
componentRegion
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
customerGateway
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
destination
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
destinationVpc
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
direction
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
elasticLoadBalancerListener
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
explanationCode
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
ingressRouteTable
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
internetGateway
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
loadBalancerArn
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
loadBalancerListenerPort
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisLoadBalancerTarget
loadBalancerTarget
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
loadBalancerTargetGroup
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [AnalysisComponent]
loadBalancerTargetGroups
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
loadBalancerTargetPort
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
missingComponent
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
natGateway
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
networkInterface
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
packetField
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
port
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [PortRange]
portRanges
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
prefixList
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
protocols
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
routeTable
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisRouteTableRoute
routeTableRoute
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
securityGroup
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisSecurityGroupRule
securityGroupRule
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [AnalysisComponent]
securityGroups
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
sourceVpc
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
state
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
subnet
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
subnetRouteTable
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
transitGateway
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
transitGatewayAttachment
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
transitGatewayRouteTable
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TransitGatewayRouteTableRoute
transitGatewayRouteTableRoute
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
vpc
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
vpcEndpoint
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
vpcPeeringConnection
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
vpnConnection
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnalysisComponent
vpnGateway
instance Prelude.NFData Explanation where
rnf :: Explanation -> ()
rnf Explanation' {Maybe Natural
Maybe [Text]
Maybe [AnalysisComponent]
Maybe [PortRange]
Maybe Text
Maybe AnalysisComponent
Maybe AnalysisLoadBalancerListener
Maybe AnalysisLoadBalancerTarget
Maybe AnalysisRouteTableRoute
Maybe AnalysisSecurityGroupRule
Maybe AnalysisAclRule
Maybe TransitGatewayRouteTableRoute
vpnGateway :: Maybe AnalysisComponent
vpnConnection :: Maybe AnalysisComponent
vpcPeeringConnection :: Maybe AnalysisComponent
vpcEndpoint :: Maybe AnalysisComponent
vpc :: Maybe AnalysisComponent
transitGatewayRouteTableRoute :: Maybe TransitGatewayRouteTableRoute
transitGatewayRouteTable :: Maybe AnalysisComponent
transitGatewayAttachment :: Maybe AnalysisComponent
transitGateway :: Maybe AnalysisComponent
subnetRouteTable :: Maybe AnalysisComponent
subnet :: Maybe AnalysisComponent
state :: Maybe Text
sourceVpc :: Maybe AnalysisComponent
securityGroups :: Maybe [AnalysisComponent]
securityGroupRule :: Maybe AnalysisSecurityGroupRule
securityGroup :: Maybe AnalysisComponent
routeTableRoute :: Maybe AnalysisRouteTableRoute
routeTable :: Maybe AnalysisComponent
protocols :: Maybe [Text]
prefixList :: Maybe AnalysisComponent
portRanges :: Maybe [PortRange]
port :: Maybe Natural
packetField :: Maybe Text
networkInterface :: Maybe AnalysisComponent
natGateway :: Maybe AnalysisComponent
missingComponent :: Maybe Text
loadBalancerTargetPort :: Maybe Natural
loadBalancerTargetGroups :: Maybe [AnalysisComponent]
loadBalancerTargetGroup :: Maybe AnalysisComponent
loadBalancerTarget :: Maybe AnalysisLoadBalancerTarget
loadBalancerListenerPort :: Maybe Natural
loadBalancerArn :: Maybe Text
internetGateway :: Maybe AnalysisComponent
ingressRouteTable :: Maybe AnalysisComponent
explanationCode :: Maybe Text
elasticLoadBalancerListener :: Maybe AnalysisComponent
direction :: Maybe Text
destinationVpc :: Maybe AnalysisComponent
destination :: Maybe AnalysisComponent
customerGateway :: Maybe AnalysisComponent
componentRegion :: Maybe Text
componentAccount :: Maybe Text
component :: Maybe AnalysisComponent
classicLoadBalancerListener :: Maybe AnalysisLoadBalancerListener
cidrs :: Maybe [Text]
availabilityZones :: Maybe [Text]
attachedTo :: Maybe AnalysisComponent
addresses :: Maybe [Text]
address :: Maybe Text
aclRule :: Maybe AnalysisAclRule
acl :: Maybe AnalysisComponent
$sel:vpnGateway:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:vpnConnection:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:vpcPeeringConnection:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:vpcEndpoint:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:vpc:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:transitGatewayRouteTableRoute:Explanation' :: Explanation -> Maybe TransitGatewayRouteTableRoute
$sel:transitGatewayRouteTable:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:transitGatewayAttachment:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:transitGateway:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:subnetRouteTable:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:subnet:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:state:Explanation' :: Explanation -> Maybe Text
$sel:sourceVpc:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:securityGroups:Explanation' :: Explanation -> Maybe [AnalysisComponent]
$sel:securityGroupRule:Explanation' :: Explanation -> Maybe AnalysisSecurityGroupRule
$sel:securityGroup:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:routeTableRoute:Explanation' :: Explanation -> Maybe AnalysisRouteTableRoute
$sel:routeTable:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:protocols:Explanation' :: Explanation -> Maybe [Text]
$sel:prefixList:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:portRanges:Explanation' :: Explanation -> Maybe [PortRange]
$sel:port:Explanation' :: Explanation -> Maybe Natural
$sel:packetField:Explanation' :: Explanation -> Maybe Text
$sel:networkInterface:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:natGateway:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:missingComponent:Explanation' :: Explanation -> Maybe Text
$sel:loadBalancerTargetPort:Explanation' :: Explanation -> Maybe Natural
$sel:loadBalancerTargetGroups:Explanation' :: Explanation -> Maybe [AnalysisComponent]
$sel:loadBalancerTargetGroup:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:loadBalancerTarget:Explanation' :: Explanation -> Maybe AnalysisLoadBalancerTarget
$sel:loadBalancerListenerPort:Explanation' :: Explanation -> Maybe Natural
$sel:loadBalancerArn:Explanation' :: Explanation -> Maybe Text
$sel:internetGateway:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:ingressRouteTable:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:explanationCode:Explanation' :: Explanation -> Maybe Text
$sel:elasticLoadBalancerListener:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:direction:Explanation' :: Explanation -> Maybe Text
$sel:destinationVpc:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:destination:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:customerGateway:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:componentRegion:Explanation' :: Explanation -> Maybe Text
$sel:componentAccount:Explanation' :: Explanation -> Maybe Text
$sel:component:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:classicLoadBalancerListener:Explanation' :: Explanation -> Maybe AnalysisLoadBalancerListener
$sel:cidrs:Explanation' :: Explanation -> Maybe [Text]
$sel:availabilityZones:Explanation' :: Explanation -> Maybe [Text]
$sel:attachedTo:Explanation' :: Explanation -> Maybe AnalysisComponent
$sel:addresses:Explanation' :: Explanation -> Maybe [Text]
$sel:address:Explanation' :: Explanation -> Maybe Text
$sel:aclRule:Explanation' :: Explanation -> Maybe AnalysisAclRule
$sel:acl:Explanation' :: Explanation -> Maybe AnalysisComponent
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe AnalysisComponent
acl
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AnalysisAclRule
aclRule
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
address
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
addresses
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AnalysisComponent
attachedTo
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
availabilityZones
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
cidrs
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AnalysisLoadBalancerListener
classicLoadBalancerListener
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AnalysisComponent
component
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
componentAccount
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
componentRegion
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AnalysisComponent
customerGateway
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AnalysisComponent
destination
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AnalysisComponent
destinationVpc
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
direction
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe AnalysisComponent
elasticLoadBalancerListener
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
explanationCode
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AnalysisComponent
ingressRouteTable
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AnalysisComponent
internetGateway
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
loadBalancerArn
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe Natural
loadBalancerListenerPort
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe AnalysisLoadBalancerTarget
loadBalancerTarget
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe AnalysisComponent
loadBalancerTargetGroup
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe [AnalysisComponent]
loadBalancerTargetGroups
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe Natural
loadBalancerTargetPort
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe Text
missingComponent
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe AnalysisComponent
natGateway
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe AnalysisComponent
networkInterface
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe Text
packetField
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe Natural
port
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe [PortRange]
portRanges
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe AnalysisComponent
prefixList
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe [Text]
protocols
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe AnalysisComponent
routeTable
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe AnalysisRouteTableRoute
routeTableRoute
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe AnalysisComponent
securityGroup
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe AnalysisSecurityGroupRule
securityGroupRule
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe [AnalysisComponent]
securityGroups
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe AnalysisComponent
sourceVpc
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe Text
state
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe AnalysisComponent
subnet
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe AnalysisComponent
subnetRouteTable
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe AnalysisComponent
transitGateway
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe AnalysisComponent
transitGatewayAttachment
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe AnalysisComponent
transitGatewayRouteTable
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe TransitGatewayRouteTableRoute
transitGatewayRouteTableRoute
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe AnalysisComponent
vpc
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe AnalysisComponent
vpcEndpoint
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe AnalysisComponent
vpcPeeringConnection
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe AnalysisComponent
vpnConnection
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
Maybe AnalysisComponent
vpnGateway