{-# 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.NetworkInterface
-- 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.NetworkInterface 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.GroupIdentifier
import Amazonka.EC2.Types.Ipv4PrefixSpecification
import Amazonka.EC2.Types.Ipv6PrefixSpecification
import Amazonka.EC2.Types.NetworkInterfaceAssociation
import Amazonka.EC2.Types.NetworkInterfaceAttachment
import Amazonka.EC2.Types.NetworkInterfaceIpv6Address
import Amazonka.EC2.Types.NetworkInterfacePrivateIpAddress
import Amazonka.EC2.Types.NetworkInterfaceStatus
import Amazonka.EC2.Types.NetworkInterfaceType
import Amazonka.EC2.Types.Tag
import qualified Amazonka.Prelude as Prelude

-- | Describes a network interface.
--
-- /See:/ 'newNetworkInterface' smart constructor.
data NetworkInterface = NetworkInterface'
  { -- | The association information for an Elastic IP address (IPv4) associated
    -- with the network interface.
    NetworkInterface -> Maybe NetworkInterfaceAssociation
association :: Prelude.Maybe NetworkInterfaceAssociation,
    -- | The network interface attachment.
    NetworkInterface -> Maybe NetworkInterfaceAttachment
attachment :: Prelude.Maybe NetworkInterfaceAttachment,
    -- | The Availability Zone.
    NetworkInterface -> Maybe Text
availabilityZone :: Prelude.Maybe Prelude.Text,
    -- | Indicates whether a network interface with an IPv6 address is
    -- unreachable from the public internet. If the value is @true@, inbound
    -- traffic from the internet is dropped and you cannot assign an elastic IP
    -- address to the network interface. The network interface is reachable
    -- from peered VPCs and resources connected through a transit gateway,
    -- including on-premises networks.
    NetworkInterface -> Maybe Bool
denyAllIgwTraffic :: Prelude.Maybe Prelude.Bool,
    -- | A description.
    NetworkInterface -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Any security groups for the network interface.
    NetworkInterface -> Maybe [GroupIdentifier]
groups :: Prelude.Maybe [GroupIdentifier],
    -- | The type of network interface.
    NetworkInterface -> Maybe NetworkInterfaceType
interfaceType :: Prelude.Maybe NetworkInterfaceType,
    -- | The IPv4 prefixes that are assigned to the network interface.
    NetworkInterface -> Maybe [Ipv4PrefixSpecification]
ipv4Prefixes :: Prelude.Maybe [Ipv4PrefixSpecification],
    -- | The IPv6 globally unique address associated with the network interface.
    NetworkInterface -> Maybe Text
ipv6Address :: Prelude.Maybe Prelude.Text,
    -- | The IPv6 addresses associated with the network interface.
    NetworkInterface -> Maybe [NetworkInterfaceIpv6Address]
ipv6Addresses :: Prelude.Maybe [NetworkInterfaceIpv6Address],
    -- | Indicates whether this is an IPv6 only network interface.
    NetworkInterface -> Maybe Bool
ipv6Native :: Prelude.Maybe Prelude.Bool,
    -- | The IPv6 prefixes that are assigned to the network interface.
    NetworkInterface -> Maybe [Ipv6PrefixSpecification]
ipv6Prefixes :: Prelude.Maybe [Ipv6PrefixSpecification],
    -- | The MAC address.
    NetworkInterface -> Maybe Text
macAddress :: Prelude.Maybe Prelude.Text,
    -- | The ID of the network interface.
    NetworkInterface -> Maybe Text
networkInterfaceId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the Outpost.
    NetworkInterface -> Maybe Text
outpostArn :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services account ID of the owner of the network
    -- interface.
    NetworkInterface -> Maybe Text
ownerId :: Prelude.Maybe Prelude.Text,
    -- | The private DNS name.
    NetworkInterface -> Maybe Text
privateDnsName :: Prelude.Maybe Prelude.Text,
    -- | The IPv4 address of the network interface within the subnet.
    NetworkInterface -> Maybe Text
privateIpAddress :: Prelude.Maybe Prelude.Text,
    -- | The private IPv4 addresses associated with the network interface.
    NetworkInterface -> Maybe [NetworkInterfacePrivateIpAddress]
privateIpAddresses :: Prelude.Maybe [NetworkInterfacePrivateIpAddress],
    -- | The alias or Amazon Web Services account ID of the principal or service
    -- that created the network interface.
    NetworkInterface -> Maybe Text
requesterId :: Prelude.Maybe Prelude.Text,
    -- | Indicates whether the network interface is being managed by Amazon Web
    -- Services.
    NetworkInterface -> Maybe Bool
requesterManaged :: Prelude.Maybe Prelude.Bool,
    -- | Indicates whether source\/destination checking is enabled.
    NetworkInterface -> Maybe Bool
sourceDestCheck :: Prelude.Maybe Prelude.Bool,
    -- | The status of the network interface.
    NetworkInterface -> Maybe NetworkInterfaceStatus
status :: Prelude.Maybe NetworkInterfaceStatus,
    -- | The ID of the subnet.
    NetworkInterface -> Maybe Text
subnetId :: Prelude.Maybe Prelude.Text,
    -- | Any tags assigned to the network interface.
    NetworkInterface -> Maybe [Tag]
tagSet :: Prelude.Maybe [Tag],
    -- | The ID of the VPC.
    NetworkInterface -> Maybe Text
vpcId :: Prelude.Maybe Prelude.Text
  }
  deriving (NetworkInterface -> NetworkInterface -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NetworkInterface -> NetworkInterface -> Bool
$c/= :: NetworkInterface -> NetworkInterface -> Bool
== :: NetworkInterface -> NetworkInterface -> Bool
$c== :: NetworkInterface -> NetworkInterface -> Bool
Prelude.Eq, ReadPrec [NetworkInterface]
ReadPrec NetworkInterface
Int -> ReadS NetworkInterface
ReadS [NetworkInterface]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NetworkInterface]
$creadListPrec :: ReadPrec [NetworkInterface]
readPrec :: ReadPrec NetworkInterface
$creadPrec :: ReadPrec NetworkInterface
readList :: ReadS [NetworkInterface]
$creadList :: ReadS [NetworkInterface]
readsPrec :: Int -> ReadS NetworkInterface
$creadsPrec :: Int -> ReadS NetworkInterface
Prelude.Read, Int -> NetworkInterface -> ShowS
[NetworkInterface] -> ShowS
NetworkInterface -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NetworkInterface] -> ShowS
$cshowList :: [NetworkInterface] -> ShowS
show :: NetworkInterface -> String
$cshow :: NetworkInterface -> String
showsPrec :: Int -> NetworkInterface -> ShowS
$cshowsPrec :: Int -> NetworkInterface -> ShowS
Prelude.Show, forall x. Rep NetworkInterface x -> NetworkInterface
forall x. NetworkInterface -> Rep NetworkInterface x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NetworkInterface x -> NetworkInterface
$cfrom :: forall x. NetworkInterface -> Rep NetworkInterface x
Prelude.Generic)

-- |
-- Create a value of 'NetworkInterface' 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:
--
-- 'association', 'networkInterface_association' - The association information for an Elastic IP address (IPv4) associated
-- with the network interface.
--
-- 'attachment', 'networkInterface_attachment' - The network interface attachment.
--
-- 'availabilityZone', 'networkInterface_availabilityZone' - The Availability Zone.
--
-- 'denyAllIgwTraffic', 'networkInterface_denyAllIgwTraffic' - Indicates whether a network interface with an IPv6 address is
-- unreachable from the public internet. If the value is @true@, inbound
-- traffic from the internet is dropped and you cannot assign an elastic IP
-- address to the network interface. The network interface is reachable
-- from peered VPCs and resources connected through a transit gateway,
-- including on-premises networks.
--
-- 'description', 'networkInterface_description' - A description.
--
-- 'groups', 'networkInterface_groups' - Any security groups for the network interface.
--
-- 'interfaceType', 'networkInterface_interfaceType' - The type of network interface.
--
-- 'ipv4Prefixes', 'networkInterface_ipv4Prefixes' - The IPv4 prefixes that are assigned to the network interface.
--
-- 'ipv6Address', 'networkInterface_ipv6Address' - The IPv6 globally unique address associated with the network interface.
--
-- 'ipv6Addresses', 'networkInterface_ipv6Addresses' - The IPv6 addresses associated with the network interface.
--
-- 'ipv6Native', 'networkInterface_ipv6Native' - Indicates whether this is an IPv6 only network interface.
--
-- 'ipv6Prefixes', 'networkInterface_ipv6Prefixes' - The IPv6 prefixes that are assigned to the network interface.
--
-- 'macAddress', 'networkInterface_macAddress' - The MAC address.
--
-- 'networkInterfaceId', 'networkInterface_networkInterfaceId' - The ID of the network interface.
--
-- 'outpostArn', 'networkInterface_outpostArn' - The Amazon Resource Name (ARN) of the Outpost.
--
-- 'ownerId', 'networkInterface_ownerId' - The Amazon Web Services account ID of the owner of the network
-- interface.
--
-- 'privateDnsName', 'networkInterface_privateDnsName' - The private DNS name.
--
-- 'privateIpAddress', 'networkInterface_privateIpAddress' - The IPv4 address of the network interface within the subnet.
--
-- 'privateIpAddresses', 'networkInterface_privateIpAddresses' - The private IPv4 addresses associated with the network interface.
--
-- 'requesterId', 'networkInterface_requesterId' - The alias or Amazon Web Services account ID of the principal or service
-- that created the network interface.
--
-- 'requesterManaged', 'networkInterface_requesterManaged' - Indicates whether the network interface is being managed by Amazon Web
-- Services.
--
-- 'sourceDestCheck', 'networkInterface_sourceDestCheck' - Indicates whether source\/destination checking is enabled.
--
-- 'status', 'networkInterface_status' - The status of the network interface.
--
-- 'subnetId', 'networkInterface_subnetId' - The ID of the subnet.
--
-- 'tagSet', 'networkInterface_tagSet' - Any tags assigned to the network interface.
--
-- 'vpcId', 'networkInterface_vpcId' - The ID of the VPC.
newNetworkInterface ::
  NetworkInterface
newNetworkInterface :: NetworkInterface
newNetworkInterface =
  NetworkInterface'
    { $sel:association:NetworkInterface' :: Maybe NetworkInterfaceAssociation
association = forall a. Maybe a
Prelude.Nothing,
      $sel:attachment:NetworkInterface' :: Maybe NetworkInterfaceAttachment
attachment = forall a. Maybe a
Prelude.Nothing,
      $sel:availabilityZone:NetworkInterface' :: Maybe Text
availabilityZone = forall a. Maybe a
Prelude.Nothing,
      $sel:denyAllIgwTraffic:NetworkInterface' :: Maybe Bool
denyAllIgwTraffic = forall a. Maybe a
Prelude.Nothing,
      $sel:description:NetworkInterface' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:groups:NetworkInterface' :: Maybe [GroupIdentifier]
groups = forall a. Maybe a
Prelude.Nothing,
      $sel:interfaceType:NetworkInterface' :: Maybe NetworkInterfaceType
interfaceType = forall a. Maybe a
Prelude.Nothing,
      $sel:ipv4Prefixes:NetworkInterface' :: Maybe [Ipv4PrefixSpecification]
ipv4Prefixes = forall a. Maybe a
Prelude.Nothing,
      $sel:ipv6Address:NetworkInterface' :: Maybe Text
ipv6Address = forall a. Maybe a
Prelude.Nothing,
      $sel:ipv6Addresses:NetworkInterface' :: Maybe [NetworkInterfaceIpv6Address]
ipv6Addresses = forall a. Maybe a
Prelude.Nothing,
      $sel:ipv6Native:NetworkInterface' :: Maybe Bool
ipv6Native = forall a. Maybe a
Prelude.Nothing,
      $sel:ipv6Prefixes:NetworkInterface' :: Maybe [Ipv6PrefixSpecification]
ipv6Prefixes = forall a. Maybe a
Prelude.Nothing,
      $sel:macAddress:NetworkInterface' :: Maybe Text
macAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:networkInterfaceId:NetworkInterface' :: Maybe Text
networkInterfaceId = forall a. Maybe a
Prelude.Nothing,
      $sel:outpostArn:NetworkInterface' :: Maybe Text
outpostArn = forall a. Maybe a
Prelude.Nothing,
      $sel:ownerId:NetworkInterface' :: Maybe Text
ownerId = forall a. Maybe a
Prelude.Nothing,
      $sel:privateDnsName:NetworkInterface' :: Maybe Text
privateDnsName = forall a. Maybe a
Prelude.Nothing,
      $sel:privateIpAddress:NetworkInterface' :: Maybe Text
privateIpAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:privateIpAddresses:NetworkInterface' :: Maybe [NetworkInterfacePrivateIpAddress]
privateIpAddresses = forall a. Maybe a
Prelude.Nothing,
      $sel:requesterId:NetworkInterface' :: Maybe Text
requesterId = forall a. Maybe a
Prelude.Nothing,
      $sel:requesterManaged:NetworkInterface' :: Maybe Bool
requesterManaged = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceDestCheck:NetworkInterface' :: Maybe Bool
sourceDestCheck = forall a. Maybe a
Prelude.Nothing,
      $sel:status:NetworkInterface' :: Maybe NetworkInterfaceStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:subnetId:NetworkInterface' :: Maybe Text
subnetId = forall a. Maybe a
Prelude.Nothing,
      $sel:tagSet:NetworkInterface' :: Maybe [Tag]
tagSet = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcId:NetworkInterface' :: Maybe Text
vpcId = forall a. Maybe a
Prelude.Nothing
    }

-- | The association information for an Elastic IP address (IPv4) associated
-- with the network interface.
networkInterface_association :: Lens.Lens' NetworkInterface (Prelude.Maybe NetworkInterfaceAssociation)
networkInterface_association :: Lens' NetworkInterface (Maybe NetworkInterfaceAssociation)
networkInterface_association = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe NetworkInterfaceAssociation
association :: Maybe NetworkInterfaceAssociation
$sel:association:NetworkInterface' :: NetworkInterface -> Maybe NetworkInterfaceAssociation
association} -> Maybe NetworkInterfaceAssociation
association) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe NetworkInterfaceAssociation
a -> NetworkInterface
s {$sel:association:NetworkInterface' :: Maybe NetworkInterfaceAssociation
association = Maybe NetworkInterfaceAssociation
a} :: NetworkInterface)

-- | The network interface attachment.
networkInterface_attachment :: Lens.Lens' NetworkInterface (Prelude.Maybe NetworkInterfaceAttachment)
networkInterface_attachment :: Lens' NetworkInterface (Maybe NetworkInterfaceAttachment)
networkInterface_attachment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe NetworkInterfaceAttachment
attachment :: Maybe NetworkInterfaceAttachment
$sel:attachment:NetworkInterface' :: NetworkInterface -> Maybe NetworkInterfaceAttachment
attachment} -> Maybe NetworkInterfaceAttachment
attachment) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe NetworkInterfaceAttachment
a -> NetworkInterface
s {$sel:attachment:NetworkInterface' :: Maybe NetworkInterfaceAttachment
attachment = Maybe NetworkInterfaceAttachment
a} :: NetworkInterface)

-- | The Availability Zone.
networkInterface_availabilityZone :: Lens.Lens' NetworkInterface (Prelude.Maybe Prelude.Text)
networkInterface_availabilityZone :: Lens' NetworkInterface (Maybe Text)
networkInterface_availabilityZone = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe Text
availabilityZone :: Maybe Text
$sel:availabilityZone:NetworkInterface' :: NetworkInterface -> Maybe Text
availabilityZone} -> Maybe Text
availabilityZone) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe Text
a -> NetworkInterface
s {$sel:availabilityZone:NetworkInterface' :: Maybe Text
availabilityZone = Maybe Text
a} :: NetworkInterface)

-- | Indicates whether a network interface with an IPv6 address is
-- unreachable from the public internet. If the value is @true@, inbound
-- traffic from the internet is dropped and you cannot assign an elastic IP
-- address to the network interface. The network interface is reachable
-- from peered VPCs and resources connected through a transit gateway,
-- including on-premises networks.
networkInterface_denyAllIgwTraffic :: Lens.Lens' NetworkInterface (Prelude.Maybe Prelude.Bool)
networkInterface_denyAllIgwTraffic :: Lens' NetworkInterface (Maybe Bool)
networkInterface_denyAllIgwTraffic = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe Bool
denyAllIgwTraffic :: Maybe Bool
$sel:denyAllIgwTraffic:NetworkInterface' :: NetworkInterface -> Maybe Bool
denyAllIgwTraffic} -> Maybe Bool
denyAllIgwTraffic) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe Bool
a -> NetworkInterface
s {$sel:denyAllIgwTraffic:NetworkInterface' :: Maybe Bool
denyAllIgwTraffic = Maybe Bool
a} :: NetworkInterface)

-- | A description.
networkInterface_description :: Lens.Lens' NetworkInterface (Prelude.Maybe Prelude.Text)
networkInterface_description :: Lens' NetworkInterface (Maybe Text)
networkInterface_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe Text
description :: Maybe Text
$sel:description:NetworkInterface' :: NetworkInterface -> Maybe Text
description} -> Maybe Text
description) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe Text
a -> NetworkInterface
s {$sel:description:NetworkInterface' :: Maybe Text
description = Maybe Text
a} :: NetworkInterface)

-- | Any security groups for the network interface.
networkInterface_groups :: Lens.Lens' NetworkInterface (Prelude.Maybe [GroupIdentifier])
networkInterface_groups :: Lens' NetworkInterface (Maybe [GroupIdentifier])
networkInterface_groups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe [GroupIdentifier]
groups :: Maybe [GroupIdentifier]
$sel:groups:NetworkInterface' :: NetworkInterface -> Maybe [GroupIdentifier]
groups} -> Maybe [GroupIdentifier]
groups) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe [GroupIdentifier]
a -> NetworkInterface
s {$sel:groups:NetworkInterface' :: Maybe [GroupIdentifier]
groups = Maybe [GroupIdentifier]
a} :: NetworkInterface) 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 type of network interface.
networkInterface_interfaceType :: Lens.Lens' NetworkInterface (Prelude.Maybe NetworkInterfaceType)
networkInterface_interfaceType :: Lens' NetworkInterface (Maybe NetworkInterfaceType)
networkInterface_interfaceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe NetworkInterfaceType
interfaceType :: Maybe NetworkInterfaceType
$sel:interfaceType:NetworkInterface' :: NetworkInterface -> Maybe NetworkInterfaceType
interfaceType} -> Maybe NetworkInterfaceType
interfaceType) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe NetworkInterfaceType
a -> NetworkInterface
s {$sel:interfaceType:NetworkInterface' :: Maybe NetworkInterfaceType
interfaceType = Maybe NetworkInterfaceType
a} :: NetworkInterface)

-- | The IPv4 prefixes that are assigned to the network interface.
networkInterface_ipv4Prefixes :: Lens.Lens' NetworkInterface (Prelude.Maybe [Ipv4PrefixSpecification])
networkInterface_ipv4Prefixes :: Lens' NetworkInterface (Maybe [Ipv4PrefixSpecification])
networkInterface_ipv4Prefixes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe [Ipv4PrefixSpecification]
ipv4Prefixes :: Maybe [Ipv4PrefixSpecification]
$sel:ipv4Prefixes:NetworkInterface' :: NetworkInterface -> Maybe [Ipv4PrefixSpecification]
ipv4Prefixes} -> Maybe [Ipv4PrefixSpecification]
ipv4Prefixes) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe [Ipv4PrefixSpecification]
a -> NetworkInterface
s {$sel:ipv4Prefixes:NetworkInterface' :: Maybe [Ipv4PrefixSpecification]
ipv4Prefixes = Maybe [Ipv4PrefixSpecification]
a} :: NetworkInterface) 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 IPv6 globally unique address associated with the network interface.
networkInterface_ipv6Address :: Lens.Lens' NetworkInterface (Prelude.Maybe Prelude.Text)
networkInterface_ipv6Address :: Lens' NetworkInterface (Maybe Text)
networkInterface_ipv6Address = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe Text
ipv6Address :: Maybe Text
$sel:ipv6Address:NetworkInterface' :: NetworkInterface -> Maybe Text
ipv6Address} -> Maybe Text
ipv6Address) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe Text
a -> NetworkInterface
s {$sel:ipv6Address:NetworkInterface' :: Maybe Text
ipv6Address = Maybe Text
a} :: NetworkInterface)

-- | The IPv6 addresses associated with the network interface.
networkInterface_ipv6Addresses :: Lens.Lens' NetworkInterface (Prelude.Maybe [NetworkInterfaceIpv6Address])
networkInterface_ipv6Addresses :: Lens' NetworkInterface (Maybe [NetworkInterfaceIpv6Address])
networkInterface_ipv6Addresses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe [NetworkInterfaceIpv6Address]
ipv6Addresses :: Maybe [NetworkInterfaceIpv6Address]
$sel:ipv6Addresses:NetworkInterface' :: NetworkInterface -> Maybe [NetworkInterfaceIpv6Address]
ipv6Addresses} -> Maybe [NetworkInterfaceIpv6Address]
ipv6Addresses) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe [NetworkInterfaceIpv6Address]
a -> NetworkInterface
s {$sel:ipv6Addresses:NetworkInterface' :: Maybe [NetworkInterfaceIpv6Address]
ipv6Addresses = Maybe [NetworkInterfaceIpv6Address]
a} :: NetworkInterface) 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

-- | Indicates whether this is an IPv6 only network interface.
networkInterface_ipv6Native :: Lens.Lens' NetworkInterface (Prelude.Maybe Prelude.Bool)
networkInterface_ipv6Native :: Lens' NetworkInterface (Maybe Bool)
networkInterface_ipv6Native = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe Bool
ipv6Native :: Maybe Bool
$sel:ipv6Native:NetworkInterface' :: NetworkInterface -> Maybe Bool
ipv6Native} -> Maybe Bool
ipv6Native) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe Bool
a -> NetworkInterface
s {$sel:ipv6Native:NetworkInterface' :: Maybe Bool
ipv6Native = Maybe Bool
a} :: NetworkInterface)

-- | The IPv6 prefixes that are assigned to the network interface.
networkInterface_ipv6Prefixes :: Lens.Lens' NetworkInterface (Prelude.Maybe [Ipv6PrefixSpecification])
networkInterface_ipv6Prefixes :: Lens' NetworkInterface (Maybe [Ipv6PrefixSpecification])
networkInterface_ipv6Prefixes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe [Ipv6PrefixSpecification]
ipv6Prefixes :: Maybe [Ipv6PrefixSpecification]
$sel:ipv6Prefixes:NetworkInterface' :: NetworkInterface -> Maybe [Ipv6PrefixSpecification]
ipv6Prefixes} -> Maybe [Ipv6PrefixSpecification]
ipv6Prefixes) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe [Ipv6PrefixSpecification]
a -> NetworkInterface
s {$sel:ipv6Prefixes:NetworkInterface' :: Maybe [Ipv6PrefixSpecification]
ipv6Prefixes = Maybe [Ipv6PrefixSpecification]
a} :: NetworkInterface) 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 MAC address.
networkInterface_macAddress :: Lens.Lens' NetworkInterface (Prelude.Maybe Prelude.Text)
networkInterface_macAddress :: Lens' NetworkInterface (Maybe Text)
networkInterface_macAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe Text
macAddress :: Maybe Text
$sel:macAddress:NetworkInterface' :: NetworkInterface -> Maybe Text
macAddress} -> Maybe Text
macAddress) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe Text
a -> NetworkInterface
s {$sel:macAddress:NetworkInterface' :: Maybe Text
macAddress = Maybe Text
a} :: NetworkInterface)

-- | The ID of the network interface.
networkInterface_networkInterfaceId :: Lens.Lens' NetworkInterface (Prelude.Maybe Prelude.Text)
networkInterface_networkInterfaceId :: Lens' NetworkInterface (Maybe Text)
networkInterface_networkInterfaceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe Text
networkInterfaceId :: Maybe Text
$sel:networkInterfaceId:NetworkInterface' :: NetworkInterface -> Maybe Text
networkInterfaceId} -> Maybe Text
networkInterfaceId) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe Text
a -> NetworkInterface
s {$sel:networkInterfaceId:NetworkInterface' :: Maybe Text
networkInterfaceId = Maybe Text
a} :: NetworkInterface)

-- | The Amazon Resource Name (ARN) of the Outpost.
networkInterface_outpostArn :: Lens.Lens' NetworkInterface (Prelude.Maybe Prelude.Text)
networkInterface_outpostArn :: Lens' NetworkInterface (Maybe Text)
networkInterface_outpostArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe Text
outpostArn :: Maybe Text
$sel:outpostArn:NetworkInterface' :: NetworkInterface -> Maybe Text
outpostArn} -> Maybe Text
outpostArn) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe Text
a -> NetworkInterface
s {$sel:outpostArn:NetworkInterface' :: Maybe Text
outpostArn = Maybe Text
a} :: NetworkInterface)

-- | The Amazon Web Services account ID of the owner of the network
-- interface.
networkInterface_ownerId :: Lens.Lens' NetworkInterface (Prelude.Maybe Prelude.Text)
networkInterface_ownerId :: Lens' NetworkInterface (Maybe Text)
networkInterface_ownerId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe Text
ownerId :: Maybe Text
$sel:ownerId:NetworkInterface' :: NetworkInterface -> Maybe Text
ownerId} -> Maybe Text
ownerId) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe Text
a -> NetworkInterface
s {$sel:ownerId:NetworkInterface' :: Maybe Text
ownerId = Maybe Text
a} :: NetworkInterface)

-- | The private DNS name.
networkInterface_privateDnsName :: Lens.Lens' NetworkInterface (Prelude.Maybe Prelude.Text)
networkInterface_privateDnsName :: Lens' NetworkInterface (Maybe Text)
networkInterface_privateDnsName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe Text
privateDnsName :: Maybe Text
$sel:privateDnsName:NetworkInterface' :: NetworkInterface -> Maybe Text
privateDnsName} -> Maybe Text
privateDnsName) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe Text
a -> NetworkInterface
s {$sel:privateDnsName:NetworkInterface' :: Maybe Text
privateDnsName = Maybe Text
a} :: NetworkInterface)

-- | The IPv4 address of the network interface within the subnet.
networkInterface_privateIpAddress :: Lens.Lens' NetworkInterface (Prelude.Maybe Prelude.Text)
networkInterface_privateIpAddress :: Lens' NetworkInterface (Maybe Text)
networkInterface_privateIpAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe Text
privateIpAddress :: Maybe Text
$sel:privateIpAddress:NetworkInterface' :: NetworkInterface -> Maybe Text
privateIpAddress} -> Maybe Text
privateIpAddress) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe Text
a -> NetworkInterface
s {$sel:privateIpAddress:NetworkInterface' :: Maybe Text
privateIpAddress = Maybe Text
a} :: NetworkInterface)

-- | The private IPv4 addresses associated with the network interface.
networkInterface_privateIpAddresses :: Lens.Lens' NetworkInterface (Prelude.Maybe [NetworkInterfacePrivateIpAddress])
networkInterface_privateIpAddresses :: Lens' NetworkInterface (Maybe [NetworkInterfacePrivateIpAddress])
networkInterface_privateIpAddresses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe [NetworkInterfacePrivateIpAddress]
privateIpAddresses :: Maybe [NetworkInterfacePrivateIpAddress]
$sel:privateIpAddresses:NetworkInterface' :: NetworkInterface -> Maybe [NetworkInterfacePrivateIpAddress]
privateIpAddresses} -> Maybe [NetworkInterfacePrivateIpAddress]
privateIpAddresses) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe [NetworkInterfacePrivateIpAddress]
a -> NetworkInterface
s {$sel:privateIpAddresses:NetworkInterface' :: Maybe [NetworkInterfacePrivateIpAddress]
privateIpAddresses = Maybe [NetworkInterfacePrivateIpAddress]
a} :: NetworkInterface) 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 alias or Amazon Web Services account ID of the principal or service
-- that created the network interface.
networkInterface_requesterId :: Lens.Lens' NetworkInterface (Prelude.Maybe Prelude.Text)
networkInterface_requesterId :: Lens' NetworkInterface (Maybe Text)
networkInterface_requesterId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe Text
requesterId :: Maybe Text
$sel:requesterId:NetworkInterface' :: NetworkInterface -> Maybe Text
requesterId} -> Maybe Text
requesterId) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe Text
a -> NetworkInterface
s {$sel:requesterId:NetworkInterface' :: Maybe Text
requesterId = Maybe Text
a} :: NetworkInterface)

-- | Indicates whether the network interface is being managed by Amazon Web
-- Services.
networkInterface_requesterManaged :: Lens.Lens' NetworkInterface (Prelude.Maybe Prelude.Bool)
networkInterface_requesterManaged :: Lens' NetworkInterface (Maybe Bool)
networkInterface_requesterManaged = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe Bool
requesterManaged :: Maybe Bool
$sel:requesterManaged:NetworkInterface' :: NetworkInterface -> Maybe Bool
requesterManaged} -> Maybe Bool
requesterManaged) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe Bool
a -> NetworkInterface
s {$sel:requesterManaged:NetworkInterface' :: Maybe Bool
requesterManaged = Maybe Bool
a} :: NetworkInterface)

-- | Indicates whether source\/destination checking is enabled.
networkInterface_sourceDestCheck :: Lens.Lens' NetworkInterface (Prelude.Maybe Prelude.Bool)
networkInterface_sourceDestCheck :: Lens' NetworkInterface (Maybe Bool)
networkInterface_sourceDestCheck = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe Bool
sourceDestCheck :: Maybe Bool
$sel:sourceDestCheck:NetworkInterface' :: NetworkInterface -> Maybe Bool
sourceDestCheck} -> Maybe Bool
sourceDestCheck) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe Bool
a -> NetworkInterface
s {$sel:sourceDestCheck:NetworkInterface' :: Maybe Bool
sourceDestCheck = Maybe Bool
a} :: NetworkInterface)

-- | The status of the network interface.
networkInterface_status :: Lens.Lens' NetworkInterface (Prelude.Maybe NetworkInterfaceStatus)
networkInterface_status :: Lens' NetworkInterface (Maybe NetworkInterfaceStatus)
networkInterface_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe NetworkInterfaceStatus
status :: Maybe NetworkInterfaceStatus
$sel:status:NetworkInterface' :: NetworkInterface -> Maybe NetworkInterfaceStatus
status} -> Maybe NetworkInterfaceStatus
status) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe NetworkInterfaceStatus
a -> NetworkInterface
s {$sel:status:NetworkInterface' :: Maybe NetworkInterfaceStatus
status = Maybe NetworkInterfaceStatus
a} :: NetworkInterface)

-- | The ID of the subnet.
networkInterface_subnetId :: Lens.Lens' NetworkInterface (Prelude.Maybe Prelude.Text)
networkInterface_subnetId :: Lens' NetworkInterface (Maybe Text)
networkInterface_subnetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe Text
subnetId :: Maybe Text
$sel:subnetId:NetworkInterface' :: NetworkInterface -> Maybe Text
subnetId} -> Maybe Text
subnetId) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe Text
a -> NetworkInterface
s {$sel:subnetId:NetworkInterface' :: Maybe Text
subnetId = Maybe Text
a} :: NetworkInterface)

-- | Any tags assigned to the network interface.
networkInterface_tagSet :: Lens.Lens' NetworkInterface (Prelude.Maybe [Tag])
networkInterface_tagSet :: Lens' NetworkInterface (Maybe [Tag])
networkInterface_tagSet = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe [Tag]
tagSet :: Maybe [Tag]
$sel:tagSet:NetworkInterface' :: NetworkInterface -> Maybe [Tag]
tagSet} -> Maybe [Tag]
tagSet) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe [Tag]
a -> NetworkInterface
s {$sel:tagSet:NetworkInterface' :: Maybe [Tag]
tagSet = Maybe [Tag]
a} :: NetworkInterface) 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 VPC.
networkInterface_vpcId :: Lens.Lens' NetworkInterface (Prelude.Maybe Prelude.Text)
networkInterface_vpcId :: Lens' NetworkInterface (Maybe Text)
networkInterface_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterface' {Maybe Text
vpcId :: Maybe Text
$sel:vpcId:NetworkInterface' :: NetworkInterface -> Maybe Text
vpcId} -> Maybe Text
vpcId) (\s :: NetworkInterface
s@NetworkInterface' {} Maybe Text
a -> NetworkInterface
s {$sel:vpcId:NetworkInterface' :: Maybe Text
vpcId = Maybe Text
a} :: NetworkInterface)

instance Data.FromXML NetworkInterface where
  parseXML :: [Node] -> Either String NetworkInterface
parseXML [Node]
x =
    Maybe NetworkInterfaceAssociation
-> Maybe NetworkInterfaceAttachment
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe [GroupIdentifier]
-> Maybe NetworkInterfaceType
-> Maybe [Ipv4PrefixSpecification]
-> Maybe Text
-> Maybe [NetworkInterfaceIpv6Address]
-> Maybe Bool
-> Maybe [Ipv6PrefixSpecification]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [NetworkInterfacePrivateIpAddress]
-> Maybe Text
-> Maybe Bool
-> Maybe Bool
-> Maybe NetworkInterfaceStatus
-> Maybe Text
-> Maybe [Tag]
-> Maybe Text
-> NetworkInterface
NetworkInterface'
      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
"association")
      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
"attachment")
      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
"availabilityZone")
      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
"denyAllIgwTraffic")
      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
"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
"groupSet"
                      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
"interfaceType")
      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
"ipv4PrefixSet"
                      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
"ipv6Address")
      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
"ipv6AddressesSet"
                      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
"ipv6Native")
      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
"ipv6PrefixSet"
                      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
"macAddress")
      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
"outpostArn")
      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
"privateDnsName")
      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
"privateIpAddress")
      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
"privateIpAddressesSet"
                      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
"requesterId")
      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
"requesterManaged")
      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
"sourceDestCheck")
      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
"status")
      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
"subnetId")
      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
"vpcId")

instance Prelude.Hashable NetworkInterface where
  hashWithSalt :: Int -> NetworkInterface -> Int
hashWithSalt Int
_salt NetworkInterface' {Maybe Bool
Maybe [GroupIdentifier]
Maybe [Ipv4PrefixSpecification]
Maybe [Ipv6PrefixSpecification]
Maybe [NetworkInterfaceIpv6Address]
Maybe [NetworkInterfacePrivateIpAddress]
Maybe [Tag]
Maybe Text
Maybe NetworkInterfaceAssociation
Maybe NetworkInterfaceAttachment
Maybe NetworkInterfaceStatus
Maybe NetworkInterfaceType
vpcId :: Maybe Text
tagSet :: Maybe [Tag]
subnetId :: Maybe Text
status :: Maybe NetworkInterfaceStatus
sourceDestCheck :: Maybe Bool
requesterManaged :: Maybe Bool
requesterId :: Maybe Text
privateIpAddresses :: Maybe [NetworkInterfacePrivateIpAddress]
privateIpAddress :: Maybe Text
privateDnsName :: Maybe Text
ownerId :: Maybe Text
outpostArn :: Maybe Text
networkInterfaceId :: Maybe Text
macAddress :: Maybe Text
ipv6Prefixes :: Maybe [Ipv6PrefixSpecification]
ipv6Native :: Maybe Bool
ipv6Addresses :: Maybe [NetworkInterfaceIpv6Address]
ipv6Address :: Maybe Text
ipv4Prefixes :: Maybe [Ipv4PrefixSpecification]
interfaceType :: Maybe NetworkInterfaceType
groups :: Maybe [GroupIdentifier]
description :: Maybe Text
denyAllIgwTraffic :: Maybe Bool
availabilityZone :: Maybe Text
attachment :: Maybe NetworkInterfaceAttachment
association :: Maybe NetworkInterfaceAssociation
$sel:vpcId:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:tagSet:NetworkInterface' :: NetworkInterface -> Maybe [Tag]
$sel:subnetId:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:status:NetworkInterface' :: NetworkInterface -> Maybe NetworkInterfaceStatus
$sel:sourceDestCheck:NetworkInterface' :: NetworkInterface -> Maybe Bool
$sel:requesterManaged:NetworkInterface' :: NetworkInterface -> Maybe Bool
$sel:requesterId:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:privateIpAddresses:NetworkInterface' :: NetworkInterface -> Maybe [NetworkInterfacePrivateIpAddress]
$sel:privateIpAddress:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:privateDnsName:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:ownerId:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:outpostArn:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:networkInterfaceId:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:macAddress:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:ipv6Prefixes:NetworkInterface' :: NetworkInterface -> Maybe [Ipv6PrefixSpecification]
$sel:ipv6Native:NetworkInterface' :: NetworkInterface -> Maybe Bool
$sel:ipv6Addresses:NetworkInterface' :: NetworkInterface -> Maybe [NetworkInterfaceIpv6Address]
$sel:ipv6Address:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:ipv4Prefixes:NetworkInterface' :: NetworkInterface -> Maybe [Ipv4PrefixSpecification]
$sel:interfaceType:NetworkInterface' :: NetworkInterface -> Maybe NetworkInterfaceType
$sel:groups:NetworkInterface' :: NetworkInterface -> Maybe [GroupIdentifier]
$sel:description:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:denyAllIgwTraffic:NetworkInterface' :: NetworkInterface -> Maybe Bool
$sel:availabilityZone:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:attachment:NetworkInterface' :: NetworkInterface -> Maybe NetworkInterfaceAttachment
$sel:association:NetworkInterface' :: NetworkInterface -> Maybe NetworkInterfaceAssociation
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NetworkInterfaceAssociation
association
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NetworkInterfaceAttachment
attachment
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
availabilityZone
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
denyAllIgwTraffic
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [GroupIdentifier]
groups
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NetworkInterfaceType
interfaceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Ipv4PrefixSpecification]
ipv4Prefixes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ipv6Address
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [NetworkInterfaceIpv6Address]
ipv6Addresses
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
ipv6Native
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Ipv6PrefixSpecification]
ipv6Prefixes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
macAddress
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
networkInterfaceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
outpostArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ownerId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
privateDnsName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
privateIpAddress
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [NetworkInterfacePrivateIpAddress]
privateIpAddresses
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
requesterId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
requesterManaged
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
sourceDestCheck
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NetworkInterfaceStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
subnetId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tagSet
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vpcId

instance Prelude.NFData NetworkInterface where
  rnf :: NetworkInterface -> ()
rnf NetworkInterface' {Maybe Bool
Maybe [GroupIdentifier]
Maybe [Ipv4PrefixSpecification]
Maybe [Ipv6PrefixSpecification]
Maybe [NetworkInterfaceIpv6Address]
Maybe [NetworkInterfacePrivateIpAddress]
Maybe [Tag]
Maybe Text
Maybe NetworkInterfaceAssociation
Maybe NetworkInterfaceAttachment
Maybe NetworkInterfaceStatus
Maybe NetworkInterfaceType
vpcId :: Maybe Text
tagSet :: Maybe [Tag]
subnetId :: Maybe Text
status :: Maybe NetworkInterfaceStatus
sourceDestCheck :: Maybe Bool
requesterManaged :: Maybe Bool
requesterId :: Maybe Text
privateIpAddresses :: Maybe [NetworkInterfacePrivateIpAddress]
privateIpAddress :: Maybe Text
privateDnsName :: Maybe Text
ownerId :: Maybe Text
outpostArn :: Maybe Text
networkInterfaceId :: Maybe Text
macAddress :: Maybe Text
ipv6Prefixes :: Maybe [Ipv6PrefixSpecification]
ipv6Native :: Maybe Bool
ipv6Addresses :: Maybe [NetworkInterfaceIpv6Address]
ipv6Address :: Maybe Text
ipv4Prefixes :: Maybe [Ipv4PrefixSpecification]
interfaceType :: Maybe NetworkInterfaceType
groups :: Maybe [GroupIdentifier]
description :: Maybe Text
denyAllIgwTraffic :: Maybe Bool
availabilityZone :: Maybe Text
attachment :: Maybe NetworkInterfaceAttachment
association :: Maybe NetworkInterfaceAssociation
$sel:vpcId:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:tagSet:NetworkInterface' :: NetworkInterface -> Maybe [Tag]
$sel:subnetId:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:status:NetworkInterface' :: NetworkInterface -> Maybe NetworkInterfaceStatus
$sel:sourceDestCheck:NetworkInterface' :: NetworkInterface -> Maybe Bool
$sel:requesterManaged:NetworkInterface' :: NetworkInterface -> Maybe Bool
$sel:requesterId:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:privateIpAddresses:NetworkInterface' :: NetworkInterface -> Maybe [NetworkInterfacePrivateIpAddress]
$sel:privateIpAddress:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:privateDnsName:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:ownerId:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:outpostArn:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:networkInterfaceId:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:macAddress:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:ipv6Prefixes:NetworkInterface' :: NetworkInterface -> Maybe [Ipv6PrefixSpecification]
$sel:ipv6Native:NetworkInterface' :: NetworkInterface -> Maybe Bool
$sel:ipv6Addresses:NetworkInterface' :: NetworkInterface -> Maybe [NetworkInterfaceIpv6Address]
$sel:ipv6Address:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:ipv4Prefixes:NetworkInterface' :: NetworkInterface -> Maybe [Ipv4PrefixSpecification]
$sel:interfaceType:NetworkInterface' :: NetworkInterface -> Maybe NetworkInterfaceType
$sel:groups:NetworkInterface' :: NetworkInterface -> Maybe [GroupIdentifier]
$sel:description:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:denyAllIgwTraffic:NetworkInterface' :: NetworkInterface -> Maybe Bool
$sel:availabilityZone:NetworkInterface' :: NetworkInterface -> Maybe Text
$sel:attachment:NetworkInterface' :: NetworkInterface -> Maybe NetworkInterfaceAttachment
$sel:association:NetworkInterface' :: NetworkInterface -> Maybe NetworkInterfaceAssociation
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe NetworkInterfaceAssociation
association
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NetworkInterfaceAttachment
attachment
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
availabilityZone
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
denyAllIgwTraffic
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 [GroupIdentifier]
groups
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NetworkInterfaceType
interfaceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Ipv4PrefixSpecification]
ipv4Prefixes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ipv6Address
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [NetworkInterfaceIpv6Address]
ipv6Addresses
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
ipv6Native
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Ipv6PrefixSpecification]
ipv6Prefixes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
macAddress
      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
outpostArn
      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 Text
privateDnsName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
privateIpAddress
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [NetworkInterfacePrivateIpAddress]
privateIpAddresses
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
requesterId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
requesterManaged
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Bool
sourceDestCheck
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NetworkInterfaceStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
subnetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tagSet
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
vpcId