{-# 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.InstanceNetworkInterface
-- 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.InstanceNetworkInterface 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.InstanceIpv4Prefix
import Amazonka.EC2.Types.InstanceIpv6Address
import Amazonka.EC2.Types.InstanceIpv6Prefix
import Amazonka.EC2.Types.InstanceNetworkInterfaceAssociation
import Amazonka.EC2.Types.InstanceNetworkInterfaceAttachment
import Amazonka.EC2.Types.InstancePrivateIpAddress
import Amazonka.EC2.Types.NetworkInterfaceStatus
import qualified Amazonka.Prelude as Prelude

-- | Describes a network interface.
--
-- /See:/ 'newInstanceNetworkInterface' smart constructor.
data InstanceNetworkInterface = InstanceNetworkInterface'
  { -- | The association information for an Elastic IPv4 associated with the
    -- network interface.
    InstanceNetworkInterface
-> Maybe InstanceNetworkInterfaceAssociation
association :: Prelude.Maybe InstanceNetworkInterfaceAssociation,
    -- | The network interface attachment.
    InstanceNetworkInterface
-> Maybe InstanceNetworkInterfaceAttachment
attachment :: Prelude.Maybe InstanceNetworkInterfaceAttachment,
    -- | The description.
    InstanceNetworkInterface -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The security groups.
    InstanceNetworkInterface -> Maybe [GroupIdentifier]
groups :: Prelude.Maybe [GroupIdentifier],
    -- | The type of network interface.
    --
    -- Valid values: @interface@ | @efa@ | @trunk@
    InstanceNetworkInterface -> Maybe Text
interfaceType :: Prelude.Maybe Prelude.Text,
    -- | The IPv4 delegated prefixes that are assigned to the network interface.
    InstanceNetworkInterface -> Maybe [InstanceIpv4Prefix]
ipv4Prefixes :: Prelude.Maybe [InstanceIpv4Prefix],
    -- | The IPv6 addresses associated with the network interface.
    InstanceNetworkInterface -> Maybe [InstanceIpv6Address]
ipv6Addresses :: Prelude.Maybe [InstanceIpv6Address],
    -- | The IPv6 delegated prefixes that are assigned to the network interface.
    InstanceNetworkInterface -> Maybe [InstanceIpv6Prefix]
ipv6Prefixes :: Prelude.Maybe [InstanceIpv6Prefix],
    -- | The MAC address.
    InstanceNetworkInterface -> Maybe Text
macAddress :: Prelude.Maybe Prelude.Text,
    -- | The ID of the network interface.
    InstanceNetworkInterface -> Maybe Text
networkInterfaceId :: Prelude.Maybe Prelude.Text,
    -- | The ID of the Amazon Web Services account that created the network
    -- interface.
    InstanceNetworkInterface -> Maybe Text
ownerId :: Prelude.Maybe Prelude.Text,
    -- | The private DNS name.
    InstanceNetworkInterface -> Maybe Text
privateDnsName :: Prelude.Maybe Prelude.Text,
    -- | The IPv4 address of the network interface within the subnet.
    InstanceNetworkInterface -> Maybe Text
privateIpAddress :: Prelude.Maybe Prelude.Text,
    -- | The private IPv4 addresses associated with the network interface.
    InstanceNetworkInterface -> Maybe [InstancePrivateIpAddress]
privateIpAddresses :: Prelude.Maybe [InstancePrivateIpAddress],
    -- | Indicates whether source\/destination checking is enabled.
    InstanceNetworkInterface -> Maybe Bool
sourceDestCheck :: Prelude.Maybe Prelude.Bool,
    -- | The status of the network interface.
    InstanceNetworkInterface -> Maybe NetworkInterfaceStatus
status :: Prelude.Maybe NetworkInterfaceStatus,
    -- | The ID of the subnet.
    InstanceNetworkInterface -> Maybe Text
subnetId :: Prelude.Maybe Prelude.Text,
    -- | The ID of the VPC.
    InstanceNetworkInterface -> Maybe Text
vpcId :: Prelude.Maybe Prelude.Text
  }
  deriving (InstanceNetworkInterface -> InstanceNetworkInterface -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InstanceNetworkInterface -> InstanceNetworkInterface -> Bool
$c/= :: InstanceNetworkInterface -> InstanceNetworkInterface -> Bool
== :: InstanceNetworkInterface -> InstanceNetworkInterface -> Bool
$c== :: InstanceNetworkInterface -> InstanceNetworkInterface -> Bool
Prelude.Eq, ReadPrec [InstanceNetworkInterface]
ReadPrec InstanceNetworkInterface
Int -> ReadS InstanceNetworkInterface
ReadS [InstanceNetworkInterface]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InstanceNetworkInterface]
$creadListPrec :: ReadPrec [InstanceNetworkInterface]
readPrec :: ReadPrec InstanceNetworkInterface
$creadPrec :: ReadPrec InstanceNetworkInterface
readList :: ReadS [InstanceNetworkInterface]
$creadList :: ReadS [InstanceNetworkInterface]
readsPrec :: Int -> ReadS InstanceNetworkInterface
$creadsPrec :: Int -> ReadS InstanceNetworkInterface
Prelude.Read, Int -> InstanceNetworkInterface -> ShowS
[InstanceNetworkInterface] -> ShowS
InstanceNetworkInterface -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InstanceNetworkInterface] -> ShowS
$cshowList :: [InstanceNetworkInterface] -> ShowS
show :: InstanceNetworkInterface -> String
$cshow :: InstanceNetworkInterface -> String
showsPrec :: Int -> InstanceNetworkInterface -> ShowS
$cshowsPrec :: Int -> InstanceNetworkInterface -> ShowS
Prelude.Show, forall x.
Rep InstanceNetworkInterface x -> InstanceNetworkInterface
forall x.
InstanceNetworkInterface -> Rep InstanceNetworkInterface x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep InstanceNetworkInterface x -> InstanceNetworkInterface
$cfrom :: forall x.
InstanceNetworkInterface -> Rep InstanceNetworkInterface x
Prelude.Generic)

-- |
-- Create a value of 'InstanceNetworkInterface' 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', 'instanceNetworkInterface_association' - The association information for an Elastic IPv4 associated with the
-- network interface.
--
-- 'attachment', 'instanceNetworkInterface_attachment' - The network interface attachment.
--
-- 'description', 'instanceNetworkInterface_description' - The description.
--
-- 'groups', 'instanceNetworkInterface_groups' - The security groups.
--
-- 'interfaceType', 'instanceNetworkInterface_interfaceType' - The type of network interface.
--
-- Valid values: @interface@ | @efa@ | @trunk@
--
-- 'ipv4Prefixes', 'instanceNetworkInterface_ipv4Prefixes' - The IPv4 delegated prefixes that are assigned to the network interface.
--
-- 'ipv6Addresses', 'instanceNetworkInterface_ipv6Addresses' - The IPv6 addresses associated with the network interface.
--
-- 'ipv6Prefixes', 'instanceNetworkInterface_ipv6Prefixes' - The IPv6 delegated prefixes that are assigned to the network interface.
--
-- 'macAddress', 'instanceNetworkInterface_macAddress' - The MAC address.
--
-- 'networkInterfaceId', 'instanceNetworkInterface_networkInterfaceId' - The ID of the network interface.
--
-- 'ownerId', 'instanceNetworkInterface_ownerId' - The ID of the Amazon Web Services account that created the network
-- interface.
--
-- 'privateDnsName', 'instanceNetworkInterface_privateDnsName' - The private DNS name.
--
-- 'privateIpAddress', 'instanceNetworkInterface_privateIpAddress' - The IPv4 address of the network interface within the subnet.
--
-- 'privateIpAddresses', 'instanceNetworkInterface_privateIpAddresses' - The private IPv4 addresses associated with the network interface.
--
-- 'sourceDestCheck', 'instanceNetworkInterface_sourceDestCheck' - Indicates whether source\/destination checking is enabled.
--
-- 'status', 'instanceNetworkInterface_status' - The status of the network interface.
--
-- 'subnetId', 'instanceNetworkInterface_subnetId' - The ID of the subnet.
--
-- 'vpcId', 'instanceNetworkInterface_vpcId' - The ID of the VPC.
newInstanceNetworkInterface ::
  InstanceNetworkInterface
newInstanceNetworkInterface :: InstanceNetworkInterface
newInstanceNetworkInterface =
  InstanceNetworkInterface'
    { $sel:association:InstanceNetworkInterface' :: Maybe InstanceNetworkInterfaceAssociation
association =
        forall a. Maybe a
Prelude.Nothing,
      $sel:attachment:InstanceNetworkInterface' :: Maybe InstanceNetworkInterfaceAttachment
attachment = forall a. Maybe a
Prelude.Nothing,
      $sel:description:InstanceNetworkInterface' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:groups:InstanceNetworkInterface' :: Maybe [GroupIdentifier]
groups = forall a. Maybe a
Prelude.Nothing,
      $sel:interfaceType:InstanceNetworkInterface' :: Maybe Text
interfaceType = forall a. Maybe a
Prelude.Nothing,
      $sel:ipv4Prefixes:InstanceNetworkInterface' :: Maybe [InstanceIpv4Prefix]
ipv4Prefixes = forall a. Maybe a
Prelude.Nothing,
      $sel:ipv6Addresses:InstanceNetworkInterface' :: Maybe [InstanceIpv6Address]
ipv6Addresses = forall a. Maybe a
Prelude.Nothing,
      $sel:ipv6Prefixes:InstanceNetworkInterface' :: Maybe [InstanceIpv6Prefix]
ipv6Prefixes = forall a. Maybe a
Prelude.Nothing,
      $sel:macAddress:InstanceNetworkInterface' :: Maybe Text
macAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:networkInterfaceId:InstanceNetworkInterface' :: Maybe Text
networkInterfaceId = forall a. Maybe a
Prelude.Nothing,
      $sel:ownerId:InstanceNetworkInterface' :: Maybe Text
ownerId = forall a. Maybe a
Prelude.Nothing,
      $sel:privateDnsName:InstanceNetworkInterface' :: Maybe Text
privateDnsName = forall a. Maybe a
Prelude.Nothing,
      $sel:privateIpAddress:InstanceNetworkInterface' :: Maybe Text
privateIpAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:privateIpAddresses:InstanceNetworkInterface' :: Maybe [InstancePrivateIpAddress]
privateIpAddresses = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceDestCheck:InstanceNetworkInterface' :: Maybe Bool
sourceDestCheck = forall a. Maybe a
Prelude.Nothing,
      $sel:status:InstanceNetworkInterface' :: Maybe NetworkInterfaceStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:subnetId:InstanceNetworkInterface' :: Maybe Text
subnetId = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcId:InstanceNetworkInterface' :: Maybe Text
vpcId = forall a. Maybe a
Prelude.Nothing
    }

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

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

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

-- | The security groups.
instanceNetworkInterface_groups :: Lens.Lens' InstanceNetworkInterface (Prelude.Maybe [GroupIdentifier])
instanceNetworkInterface_groups :: Lens' InstanceNetworkInterface (Maybe [GroupIdentifier])
instanceNetworkInterface_groups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterface' {Maybe [GroupIdentifier]
groups :: Maybe [GroupIdentifier]
$sel:groups:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe [GroupIdentifier]
groups} -> Maybe [GroupIdentifier]
groups) (\s :: InstanceNetworkInterface
s@InstanceNetworkInterface' {} Maybe [GroupIdentifier]
a -> InstanceNetworkInterface
s {$sel:groups:InstanceNetworkInterface' :: Maybe [GroupIdentifier]
groups = Maybe [GroupIdentifier]
a} :: InstanceNetworkInterface) 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.
--
-- Valid values: @interface@ | @efa@ | @trunk@
instanceNetworkInterface_interfaceType :: Lens.Lens' InstanceNetworkInterface (Prelude.Maybe Prelude.Text)
instanceNetworkInterface_interfaceType :: Lens' InstanceNetworkInterface (Maybe Text)
instanceNetworkInterface_interfaceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterface' {Maybe Text
interfaceType :: Maybe Text
$sel:interfaceType:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Text
interfaceType} -> Maybe Text
interfaceType) (\s :: InstanceNetworkInterface
s@InstanceNetworkInterface' {} Maybe Text
a -> InstanceNetworkInterface
s {$sel:interfaceType:InstanceNetworkInterface' :: Maybe Text
interfaceType = Maybe Text
a} :: InstanceNetworkInterface)

-- | The IPv4 delegated prefixes that are assigned to the network interface.
instanceNetworkInterface_ipv4Prefixes :: Lens.Lens' InstanceNetworkInterface (Prelude.Maybe [InstanceIpv4Prefix])
instanceNetworkInterface_ipv4Prefixes :: Lens' InstanceNetworkInterface (Maybe [InstanceIpv4Prefix])
instanceNetworkInterface_ipv4Prefixes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterface' {Maybe [InstanceIpv4Prefix]
ipv4Prefixes :: Maybe [InstanceIpv4Prefix]
$sel:ipv4Prefixes:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe [InstanceIpv4Prefix]
ipv4Prefixes} -> Maybe [InstanceIpv4Prefix]
ipv4Prefixes) (\s :: InstanceNetworkInterface
s@InstanceNetworkInterface' {} Maybe [InstanceIpv4Prefix]
a -> InstanceNetworkInterface
s {$sel:ipv4Prefixes:InstanceNetworkInterface' :: Maybe [InstanceIpv4Prefix]
ipv4Prefixes = Maybe [InstanceIpv4Prefix]
a} :: InstanceNetworkInterface) 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 addresses associated with the network interface.
instanceNetworkInterface_ipv6Addresses :: Lens.Lens' InstanceNetworkInterface (Prelude.Maybe [InstanceIpv6Address])
instanceNetworkInterface_ipv6Addresses :: Lens' InstanceNetworkInterface (Maybe [InstanceIpv6Address])
instanceNetworkInterface_ipv6Addresses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterface' {Maybe [InstanceIpv6Address]
ipv6Addresses :: Maybe [InstanceIpv6Address]
$sel:ipv6Addresses:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe [InstanceIpv6Address]
ipv6Addresses} -> Maybe [InstanceIpv6Address]
ipv6Addresses) (\s :: InstanceNetworkInterface
s@InstanceNetworkInterface' {} Maybe [InstanceIpv6Address]
a -> InstanceNetworkInterface
s {$sel:ipv6Addresses:InstanceNetworkInterface' :: Maybe [InstanceIpv6Address]
ipv6Addresses = Maybe [InstanceIpv6Address]
a} :: InstanceNetworkInterface) 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 delegated prefixes that are assigned to the network interface.
instanceNetworkInterface_ipv6Prefixes :: Lens.Lens' InstanceNetworkInterface (Prelude.Maybe [InstanceIpv6Prefix])
instanceNetworkInterface_ipv6Prefixes :: Lens' InstanceNetworkInterface (Maybe [InstanceIpv6Prefix])
instanceNetworkInterface_ipv6Prefixes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterface' {Maybe [InstanceIpv6Prefix]
ipv6Prefixes :: Maybe [InstanceIpv6Prefix]
$sel:ipv6Prefixes:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe [InstanceIpv6Prefix]
ipv6Prefixes} -> Maybe [InstanceIpv6Prefix]
ipv6Prefixes) (\s :: InstanceNetworkInterface
s@InstanceNetworkInterface' {} Maybe [InstanceIpv6Prefix]
a -> InstanceNetworkInterface
s {$sel:ipv6Prefixes:InstanceNetworkInterface' :: Maybe [InstanceIpv6Prefix]
ipv6Prefixes = Maybe [InstanceIpv6Prefix]
a} :: InstanceNetworkInterface) 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.
instanceNetworkInterface_macAddress :: Lens.Lens' InstanceNetworkInterface (Prelude.Maybe Prelude.Text)
instanceNetworkInterface_macAddress :: Lens' InstanceNetworkInterface (Maybe Text)
instanceNetworkInterface_macAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterface' {Maybe Text
macAddress :: Maybe Text
$sel:macAddress:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Text
macAddress} -> Maybe Text
macAddress) (\s :: InstanceNetworkInterface
s@InstanceNetworkInterface' {} Maybe Text
a -> InstanceNetworkInterface
s {$sel:macAddress:InstanceNetworkInterface' :: Maybe Text
macAddress = Maybe Text
a} :: InstanceNetworkInterface)

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

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

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

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

-- | The private IPv4 addresses associated with the network interface.
instanceNetworkInterface_privateIpAddresses :: Lens.Lens' InstanceNetworkInterface (Prelude.Maybe [InstancePrivateIpAddress])
instanceNetworkInterface_privateIpAddresses :: Lens' InstanceNetworkInterface (Maybe [InstancePrivateIpAddress])
instanceNetworkInterface_privateIpAddresses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterface' {Maybe [InstancePrivateIpAddress]
privateIpAddresses :: Maybe [InstancePrivateIpAddress]
$sel:privateIpAddresses:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe [InstancePrivateIpAddress]
privateIpAddresses} -> Maybe [InstancePrivateIpAddress]
privateIpAddresses) (\s :: InstanceNetworkInterface
s@InstanceNetworkInterface' {} Maybe [InstancePrivateIpAddress]
a -> InstanceNetworkInterface
s {$sel:privateIpAddresses:InstanceNetworkInterface' :: Maybe [InstancePrivateIpAddress]
privateIpAddresses = Maybe [InstancePrivateIpAddress]
a} :: InstanceNetworkInterface) 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 source\/destination checking is enabled.
instanceNetworkInterface_sourceDestCheck :: Lens.Lens' InstanceNetworkInterface (Prelude.Maybe Prelude.Bool)
instanceNetworkInterface_sourceDestCheck :: Lens' InstanceNetworkInterface (Maybe Bool)
instanceNetworkInterface_sourceDestCheck = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterface' {Maybe Bool
sourceDestCheck :: Maybe Bool
$sel:sourceDestCheck:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Bool
sourceDestCheck} -> Maybe Bool
sourceDestCheck) (\s :: InstanceNetworkInterface
s@InstanceNetworkInterface' {} Maybe Bool
a -> InstanceNetworkInterface
s {$sel:sourceDestCheck:InstanceNetworkInterface' :: Maybe Bool
sourceDestCheck = Maybe Bool
a} :: InstanceNetworkInterface)

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

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

-- | The ID of the VPC.
instanceNetworkInterface_vpcId :: Lens.Lens' InstanceNetworkInterface (Prelude.Maybe Prelude.Text)
instanceNetworkInterface_vpcId :: Lens' InstanceNetworkInterface (Maybe Text)
instanceNetworkInterface_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterface' {Maybe Text
vpcId :: Maybe Text
$sel:vpcId:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Text
vpcId} -> Maybe Text
vpcId) (\s :: InstanceNetworkInterface
s@InstanceNetworkInterface' {} Maybe Text
a -> InstanceNetworkInterface
s {$sel:vpcId:InstanceNetworkInterface' :: Maybe Text
vpcId = Maybe Text
a} :: InstanceNetworkInterface)

instance Data.FromXML InstanceNetworkInterface where
  parseXML :: [Node] -> Either String InstanceNetworkInterface
parseXML [Node]
x =
    Maybe InstanceNetworkInterfaceAssociation
-> Maybe InstanceNetworkInterfaceAttachment
-> Maybe Text
-> Maybe [GroupIdentifier]
-> Maybe Text
-> Maybe [InstanceIpv4Prefix]
-> Maybe [InstanceIpv6Address]
-> Maybe [InstanceIpv6Prefix]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [InstancePrivateIpAddress]
-> Maybe Bool
-> Maybe NetworkInterfaceStatus
-> Maybe Text
-> Maybe Text
-> InstanceNetworkInterface
InstanceNetworkInterface'
      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
"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
"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
"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
"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
"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
"vpcId")

instance Prelude.Hashable InstanceNetworkInterface where
  hashWithSalt :: Int -> InstanceNetworkInterface -> Int
hashWithSalt Int
_salt InstanceNetworkInterface' {Maybe Bool
Maybe [GroupIdentifier]
Maybe [InstanceIpv4Prefix]
Maybe [InstanceIpv6Address]
Maybe [InstanceIpv6Prefix]
Maybe [InstancePrivateIpAddress]
Maybe Text
Maybe InstanceNetworkInterfaceAssociation
Maybe InstanceNetworkInterfaceAttachment
Maybe NetworkInterfaceStatus
vpcId :: Maybe Text
subnetId :: Maybe Text
status :: Maybe NetworkInterfaceStatus
sourceDestCheck :: Maybe Bool
privateIpAddresses :: Maybe [InstancePrivateIpAddress]
privateIpAddress :: Maybe Text
privateDnsName :: Maybe Text
ownerId :: Maybe Text
networkInterfaceId :: Maybe Text
macAddress :: Maybe Text
ipv6Prefixes :: Maybe [InstanceIpv6Prefix]
ipv6Addresses :: Maybe [InstanceIpv6Address]
ipv4Prefixes :: Maybe [InstanceIpv4Prefix]
interfaceType :: Maybe Text
groups :: Maybe [GroupIdentifier]
description :: Maybe Text
attachment :: Maybe InstanceNetworkInterfaceAttachment
association :: Maybe InstanceNetworkInterfaceAssociation
$sel:vpcId:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Text
$sel:subnetId:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Text
$sel:status:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe NetworkInterfaceStatus
$sel:sourceDestCheck:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Bool
$sel:privateIpAddresses:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe [InstancePrivateIpAddress]
$sel:privateIpAddress:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Text
$sel:privateDnsName:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Text
$sel:ownerId:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Text
$sel:networkInterfaceId:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Text
$sel:macAddress:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Text
$sel:ipv6Prefixes:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe [InstanceIpv6Prefix]
$sel:ipv6Addresses:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe [InstanceIpv6Address]
$sel:ipv4Prefixes:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe [InstanceIpv4Prefix]
$sel:interfaceType:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Text
$sel:groups:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe [GroupIdentifier]
$sel:description:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Text
$sel:attachment:InstanceNetworkInterface' :: InstanceNetworkInterface
-> Maybe InstanceNetworkInterfaceAttachment
$sel:association:InstanceNetworkInterface' :: InstanceNetworkInterface
-> Maybe InstanceNetworkInterfaceAssociation
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InstanceNetworkInterfaceAssociation
association
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InstanceNetworkInterfaceAttachment
attachment
      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 Text
interfaceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [InstanceIpv4Prefix]
ipv4Prefixes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [InstanceIpv6Address]
ipv6Addresses
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [InstanceIpv6Prefix]
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
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 [InstancePrivateIpAddress]
privateIpAddresses
      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 Text
vpcId

instance Prelude.NFData InstanceNetworkInterface where
  rnf :: InstanceNetworkInterface -> ()
rnf InstanceNetworkInterface' {Maybe Bool
Maybe [GroupIdentifier]
Maybe [InstanceIpv4Prefix]
Maybe [InstanceIpv6Address]
Maybe [InstanceIpv6Prefix]
Maybe [InstancePrivateIpAddress]
Maybe Text
Maybe InstanceNetworkInterfaceAssociation
Maybe InstanceNetworkInterfaceAttachment
Maybe NetworkInterfaceStatus
vpcId :: Maybe Text
subnetId :: Maybe Text
status :: Maybe NetworkInterfaceStatus
sourceDestCheck :: Maybe Bool
privateIpAddresses :: Maybe [InstancePrivateIpAddress]
privateIpAddress :: Maybe Text
privateDnsName :: Maybe Text
ownerId :: Maybe Text
networkInterfaceId :: Maybe Text
macAddress :: Maybe Text
ipv6Prefixes :: Maybe [InstanceIpv6Prefix]
ipv6Addresses :: Maybe [InstanceIpv6Address]
ipv4Prefixes :: Maybe [InstanceIpv4Prefix]
interfaceType :: Maybe Text
groups :: Maybe [GroupIdentifier]
description :: Maybe Text
attachment :: Maybe InstanceNetworkInterfaceAttachment
association :: Maybe InstanceNetworkInterfaceAssociation
$sel:vpcId:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Text
$sel:subnetId:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Text
$sel:status:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe NetworkInterfaceStatus
$sel:sourceDestCheck:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Bool
$sel:privateIpAddresses:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe [InstancePrivateIpAddress]
$sel:privateIpAddress:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Text
$sel:privateDnsName:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Text
$sel:ownerId:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Text
$sel:networkInterfaceId:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Text
$sel:macAddress:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Text
$sel:ipv6Prefixes:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe [InstanceIpv6Prefix]
$sel:ipv6Addresses:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe [InstanceIpv6Address]
$sel:ipv4Prefixes:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe [InstanceIpv4Prefix]
$sel:interfaceType:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Text
$sel:groups:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe [GroupIdentifier]
$sel:description:InstanceNetworkInterface' :: InstanceNetworkInterface -> Maybe Text
$sel:attachment:InstanceNetworkInterface' :: InstanceNetworkInterface
-> Maybe InstanceNetworkInterfaceAttachment
$sel:association:InstanceNetworkInterface' :: InstanceNetworkInterface
-> Maybe InstanceNetworkInterfaceAssociation
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe InstanceNetworkInterfaceAssociation
association
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InstanceNetworkInterfaceAttachment
attachment
      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 Text
interfaceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [InstanceIpv4Prefix]
ipv4Prefixes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [InstanceIpv6Address]
ipv6Addresses
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [InstanceIpv6Prefix]
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
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 [InstancePrivateIpAddress]
privateIpAddresses
      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 Text
vpcId