{-# 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.Subnet
-- 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.Subnet 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.PrivateDnsNameOptionsOnLaunch
import Amazonka.EC2.Types.SubnetIpv6CidrBlockAssociation
import Amazonka.EC2.Types.SubnetState
import Amazonka.EC2.Types.Tag
import qualified Amazonka.Prelude as Prelude

-- | Describes a subnet.
--
-- /See:/ 'newSubnet' smart constructor.
data Subnet = Subnet'
  { -- | Indicates whether a network interface created in this subnet (including
    -- a network interface created by RunInstances) receives an IPv6 address.
    Subnet -> Maybe Bool
assignIpv6AddressOnCreation :: Prelude.Maybe Prelude.Bool,
    -- | The AZ ID of the subnet.
    Subnet -> Maybe Text
availabilityZoneId :: Prelude.Maybe Prelude.Text,
    -- | The customer-owned IPv4 address pool associated with the subnet.
    Subnet -> Maybe Text
customerOwnedIpv4Pool :: Prelude.Maybe Prelude.Text,
    -- | Indicates whether this is the default subnet for the Availability Zone.
    Subnet -> Maybe Bool
defaultForAz :: Prelude.Maybe Prelude.Bool,
    -- | Indicates whether DNS queries made to the Amazon-provided DNS Resolver
    -- in this subnet should return synthetic IPv6 addresses for IPv4-only
    -- destinations.
    Subnet -> Maybe Bool
enableDns64 :: Prelude.Maybe Prelude.Bool,
    -- | Indicates the device position for local network interfaces in this
    -- subnet. For example, @1@ indicates local network interfaces in this
    -- subnet are the secondary network interface (eth1).
    Subnet -> Maybe Int
enableLniAtDeviceIndex :: Prelude.Maybe Prelude.Int,
    -- | Information about the IPv6 CIDR blocks associated with the subnet.
    Subnet -> Maybe [SubnetIpv6CidrBlockAssociation]
ipv6CidrBlockAssociationSet :: Prelude.Maybe [SubnetIpv6CidrBlockAssociation],
    -- | Indicates whether this is an IPv6 only subnet.
    Subnet -> Maybe Bool
ipv6Native :: Prelude.Maybe Prelude.Bool,
    -- | Indicates whether a network interface created in this subnet (including
    -- a network interface created by RunInstances) receives a customer-owned
    -- IPv4 address.
    Subnet -> Maybe Bool
mapCustomerOwnedIpOnLaunch :: Prelude.Maybe Prelude.Bool,
    -- | Indicates whether instances launched in this subnet receive a public
    -- IPv4 address.
    Subnet -> Maybe Bool
mapPublicIpOnLaunch :: Prelude.Maybe Prelude.Bool,
    -- | The Amazon Resource Name (ARN) of the Outpost.
    Subnet -> Maybe Text
outpostArn :: Prelude.Maybe Prelude.Text,
    -- | The ID of the Amazon Web Services account that owns the subnet.
    Subnet -> Maybe Text
ownerId :: Prelude.Maybe Prelude.Text,
    -- | The type of hostnames to assign to instances in the subnet at launch. An
    -- instance hostname is based on the IPv4 address or ID of the instance.
    Subnet -> Maybe PrivateDnsNameOptionsOnLaunch
privateDnsNameOptionsOnLaunch :: Prelude.Maybe PrivateDnsNameOptionsOnLaunch,
    -- | The Amazon Resource Name (ARN) of the subnet.
    Subnet -> Maybe Text
subnetArn :: Prelude.Maybe Prelude.Text,
    -- | Any tags assigned to the subnet.
    Subnet -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The Availability Zone of the subnet.
    Subnet -> Text
availabilityZone :: Prelude.Text,
    -- | The number of unused private IPv4 addresses in the subnet. The IPv4
    -- addresses for any stopped instances are considered unavailable.
    Subnet -> Int
availableIpAddressCount :: Prelude.Int,
    -- | The IPv4 CIDR block assigned to the subnet.
    Subnet -> Text
cidrBlock :: Prelude.Text,
    -- | The current state of the subnet.
    Subnet -> SubnetState
state :: SubnetState,
    -- | The ID of the subnet.
    Subnet -> Text
subnetId :: Prelude.Text,
    -- | The ID of the VPC the subnet is in.
    Subnet -> Text
vpcId :: Prelude.Text
  }
  deriving (Subnet -> Subnet -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Subnet -> Subnet -> Bool
$c/= :: Subnet -> Subnet -> Bool
== :: Subnet -> Subnet -> Bool
$c== :: Subnet -> Subnet -> Bool
Prelude.Eq, ReadPrec [Subnet]
ReadPrec Subnet
Int -> ReadS Subnet
ReadS [Subnet]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Subnet]
$creadListPrec :: ReadPrec [Subnet]
readPrec :: ReadPrec Subnet
$creadPrec :: ReadPrec Subnet
readList :: ReadS [Subnet]
$creadList :: ReadS [Subnet]
readsPrec :: Int -> ReadS Subnet
$creadsPrec :: Int -> ReadS Subnet
Prelude.Read, Int -> Subnet -> ShowS
[Subnet] -> ShowS
Subnet -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Subnet] -> ShowS
$cshowList :: [Subnet] -> ShowS
show :: Subnet -> String
$cshow :: Subnet -> String
showsPrec :: Int -> Subnet -> ShowS
$cshowsPrec :: Int -> Subnet -> ShowS
Prelude.Show, forall x. Rep Subnet x -> Subnet
forall x. Subnet -> Rep Subnet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Subnet x -> Subnet
$cfrom :: forall x. Subnet -> Rep Subnet x
Prelude.Generic)

-- |
-- Create a value of 'Subnet' 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:
--
-- 'assignIpv6AddressOnCreation', 'subnet_assignIpv6AddressOnCreation' - Indicates whether a network interface created in this subnet (including
-- a network interface created by RunInstances) receives an IPv6 address.
--
-- 'availabilityZoneId', 'subnet_availabilityZoneId' - The AZ ID of the subnet.
--
-- 'customerOwnedIpv4Pool', 'subnet_customerOwnedIpv4Pool' - The customer-owned IPv4 address pool associated with the subnet.
--
-- 'defaultForAz', 'subnet_defaultForAz' - Indicates whether this is the default subnet for the Availability Zone.
--
-- 'enableDns64', 'subnet_enableDns64' - Indicates whether DNS queries made to the Amazon-provided DNS Resolver
-- in this subnet should return synthetic IPv6 addresses for IPv4-only
-- destinations.
--
-- 'enableLniAtDeviceIndex', 'subnet_enableLniAtDeviceIndex' - Indicates the device position for local network interfaces in this
-- subnet. For example, @1@ indicates local network interfaces in this
-- subnet are the secondary network interface (eth1).
--
-- 'ipv6CidrBlockAssociationSet', 'subnet_ipv6CidrBlockAssociationSet' - Information about the IPv6 CIDR blocks associated with the subnet.
--
-- 'ipv6Native', 'subnet_ipv6Native' - Indicates whether this is an IPv6 only subnet.
--
-- 'mapCustomerOwnedIpOnLaunch', 'subnet_mapCustomerOwnedIpOnLaunch' - Indicates whether a network interface created in this subnet (including
-- a network interface created by RunInstances) receives a customer-owned
-- IPv4 address.
--
-- 'mapPublicIpOnLaunch', 'subnet_mapPublicIpOnLaunch' - Indicates whether instances launched in this subnet receive a public
-- IPv4 address.
--
-- 'outpostArn', 'subnet_outpostArn' - The Amazon Resource Name (ARN) of the Outpost.
--
-- 'ownerId', 'subnet_ownerId' - The ID of the Amazon Web Services account that owns the subnet.
--
-- 'privateDnsNameOptionsOnLaunch', 'subnet_privateDnsNameOptionsOnLaunch' - The type of hostnames to assign to instances in the subnet at launch. An
-- instance hostname is based on the IPv4 address or ID of the instance.
--
-- 'subnetArn', 'subnet_subnetArn' - The Amazon Resource Name (ARN) of the subnet.
--
-- 'tags', 'subnet_tags' - Any tags assigned to the subnet.
--
-- 'availabilityZone', 'subnet_availabilityZone' - The Availability Zone of the subnet.
--
-- 'availableIpAddressCount', 'subnet_availableIpAddressCount' - The number of unused private IPv4 addresses in the subnet. The IPv4
-- addresses for any stopped instances are considered unavailable.
--
-- 'cidrBlock', 'subnet_cidrBlock' - The IPv4 CIDR block assigned to the subnet.
--
-- 'state', 'subnet_state' - The current state of the subnet.
--
-- 'subnetId', 'subnet_subnetId' - The ID of the subnet.
--
-- 'vpcId', 'subnet_vpcId' - The ID of the VPC the subnet is in.
newSubnet ::
  -- | 'availabilityZone'
  Prelude.Text ->
  -- | 'availableIpAddressCount'
  Prelude.Int ->
  -- | 'cidrBlock'
  Prelude.Text ->
  -- | 'state'
  SubnetState ->
  -- | 'subnetId'
  Prelude.Text ->
  -- | 'vpcId'
  Prelude.Text ->
  Subnet
newSubnet :: Text -> Int -> Text -> SubnetState -> Text -> Text -> Subnet
newSubnet
  Text
pAvailabilityZone_
  Int
pAvailableIpAddressCount_
  Text
pCidrBlock_
  SubnetState
pState_
  Text
pSubnetId_
  Text
pVpcId_ =
    Subnet'
      { $sel:assignIpv6AddressOnCreation:Subnet' :: Maybe Bool
assignIpv6AddressOnCreation =
          forall a. Maybe a
Prelude.Nothing,
        $sel:availabilityZoneId:Subnet' :: Maybe Text
availabilityZoneId = forall a. Maybe a
Prelude.Nothing,
        $sel:customerOwnedIpv4Pool:Subnet' :: Maybe Text
customerOwnedIpv4Pool = forall a. Maybe a
Prelude.Nothing,
        $sel:defaultForAz:Subnet' :: Maybe Bool
defaultForAz = forall a. Maybe a
Prelude.Nothing,
        $sel:enableDns64:Subnet' :: Maybe Bool
enableDns64 = forall a. Maybe a
Prelude.Nothing,
        $sel:enableLniAtDeviceIndex:Subnet' :: Maybe Int
enableLniAtDeviceIndex = forall a. Maybe a
Prelude.Nothing,
        $sel:ipv6CidrBlockAssociationSet:Subnet' :: Maybe [SubnetIpv6CidrBlockAssociation]
ipv6CidrBlockAssociationSet = forall a. Maybe a
Prelude.Nothing,
        $sel:ipv6Native:Subnet' :: Maybe Bool
ipv6Native = forall a. Maybe a
Prelude.Nothing,
        $sel:mapCustomerOwnedIpOnLaunch:Subnet' :: Maybe Bool
mapCustomerOwnedIpOnLaunch = forall a. Maybe a
Prelude.Nothing,
        $sel:mapPublicIpOnLaunch:Subnet' :: Maybe Bool
mapPublicIpOnLaunch = forall a. Maybe a
Prelude.Nothing,
        $sel:outpostArn:Subnet' :: Maybe Text
outpostArn = forall a. Maybe a
Prelude.Nothing,
        $sel:ownerId:Subnet' :: Maybe Text
ownerId = forall a. Maybe a
Prelude.Nothing,
        $sel:privateDnsNameOptionsOnLaunch:Subnet' :: Maybe PrivateDnsNameOptionsOnLaunch
privateDnsNameOptionsOnLaunch = forall a. Maybe a
Prelude.Nothing,
        $sel:subnetArn:Subnet' :: Maybe Text
subnetArn = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:Subnet' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:availabilityZone:Subnet' :: Text
availabilityZone = Text
pAvailabilityZone_,
        $sel:availableIpAddressCount:Subnet' :: Int
availableIpAddressCount = Int
pAvailableIpAddressCount_,
        $sel:cidrBlock:Subnet' :: Text
cidrBlock = Text
pCidrBlock_,
        $sel:state:Subnet' :: SubnetState
state = SubnetState
pState_,
        $sel:subnetId:Subnet' :: Text
subnetId = Text
pSubnetId_,
        $sel:vpcId:Subnet' :: Text
vpcId = Text
pVpcId_
      }

-- | Indicates whether a network interface created in this subnet (including
-- a network interface created by RunInstances) receives an IPv6 address.
subnet_assignIpv6AddressOnCreation :: Lens.Lens' Subnet (Prelude.Maybe Prelude.Bool)
subnet_assignIpv6AddressOnCreation :: Lens' Subnet (Maybe Bool)
subnet_assignIpv6AddressOnCreation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subnet' {Maybe Bool
assignIpv6AddressOnCreation :: Maybe Bool
$sel:assignIpv6AddressOnCreation:Subnet' :: Subnet -> Maybe Bool
assignIpv6AddressOnCreation} -> Maybe Bool
assignIpv6AddressOnCreation) (\s :: Subnet
s@Subnet' {} Maybe Bool
a -> Subnet
s {$sel:assignIpv6AddressOnCreation:Subnet' :: Maybe Bool
assignIpv6AddressOnCreation = Maybe Bool
a} :: Subnet)

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

-- | The customer-owned IPv4 address pool associated with the subnet.
subnet_customerOwnedIpv4Pool :: Lens.Lens' Subnet (Prelude.Maybe Prelude.Text)
subnet_customerOwnedIpv4Pool :: Lens' Subnet (Maybe Text)
subnet_customerOwnedIpv4Pool = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subnet' {Maybe Text
customerOwnedIpv4Pool :: Maybe Text
$sel:customerOwnedIpv4Pool:Subnet' :: Subnet -> Maybe Text
customerOwnedIpv4Pool} -> Maybe Text
customerOwnedIpv4Pool) (\s :: Subnet
s@Subnet' {} Maybe Text
a -> Subnet
s {$sel:customerOwnedIpv4Pool:Subnet' :: Maybe Text
customerOwnedIpv4Pool = Maybe Text
a} :: Subnet)

-- | Indicates whether this is the default subnet for the Availability Zone.
subnet_defaultForAz :: Lens.Lens' Subnet (Prelude.Maybe Prelude.Bool)
subnet_defaultForAz :: Lens' Subnet (Maybe Bool)
subnet_defaultForAz = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subnet' {Maybe Bool
defaultForAz :: Maybe Bool
$sel:defaultForAz:Subnet' :: Subnet -> Maybe Bool
defaultForAz} -> Maybe Bool
defaultForAz) (\s :: Subnet
s@Subnet' {} Maybe Bool
a -> Subnet
s {$sel:defaultForAz:Subnet' :: Maybe Bool
defaultForAz = Maybe Bool
a} :: Subnet)

-- | Indicates whether DNS queries made to the Amazon-provided DNS Resolver
-- in this subnet should return synthetic IPv6 addresses for IPv4-only
-- destinations.
subnet_enableDns64 :: Lens.Lens' Subnet (Prelude.Maybe Prelude.Bool)
subnet_enableDns64 :: Lens' Subnet (Maybe Bool)
subnet_enableDns64 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subnet' {Maybe Bool
enableDns64 :: Maybe Bool
$sel:enableDns64:Subnet' :: Subnet -> Maybe Bool
enableDns64} -> Maybe Bool
enableDns64) (\s :: Subnet
s@Subnet' {} Maybe Bool
a -> Subnet
s {$sel:enableDns64:Subnet' :: Maybe Bool
enableDns64 = Maybe Bool
a} :: Subnet)

-- | Indicates the device position for local network interfaces in this
-- subnet. For example, @1@ indicates local network interfaces in this
-- subnet are the secondary network interface (eth1).
subnet_enableLniAtDeviceIndex :: Lens.Lens' Subnet (Prelude.Maybe Prelude.Int)
subnet_enableLniAtDeviceIndex :: Lens' Subnet (Maybe Int)
subnet_enableLniAtDeviceIndex = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subnet' {Maybe Int
enableLniAtDeviceIndex :: Maybe Int
$sel:enableLniAtDeviceIndex:Subnet' :: Subnet -> Maybe Int
enableLniAtDeviceIndex} -> Maybe Int
enableLniAtDeviceIndex) (\s :: Subnet
s@Subnet' {} Maybe Int
a -> Subnet
s {$sel:enableLniAtDeviceIndex:Subnet' :: Maybe Int
enableLniAtDeviceIndex = Maybe Int
a} :: Subnet)

-- | Information about the IPv6 CIDR blocks associated with the subnet.
subnet_ipv6CidrBlockAssociationSet :: Lens.Lens' Subnet (Prelude.Maybe [SubnetIpv6CidrBlockAssociation])
subnet_ipv6CidrBlockAssociationSet :: Lens' Subnet (Maybe [SubnetIpv6CidrBlockAssociation])
subnet_ipv6CidrBlockAssociationSet = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subnet' {Maybe [SubnetIpv6CidrBlockAssociation]
ipv6CidrBlockAssociationSet :: Maybe [SubnetIpv6CidrBlockAssociation]
$sel:ipv6CidrBlockAssociationSet:Subnet' :: Subnet -> Maybe [SubnetIpv6CidrBlockAssociation]
ipv6CidrBlockAssociationSet} -> Maybe [SubnetIpv6CidrBlockAssociation]
ipv6CidrBlockAssociationSet) (\s :: Subnet
s@Subnet' {} Maybe [SubnetIpv6CidrBlockAssociation]
a -> Subnet
s {$sel:ipv6CidrBlockAssociationSet:Subnet' :: Maybe [SubnetIpv6CidrBlockAssociation]
ipv6CidrBlockAssociationSet = Maybe [SubnetIpv6CidrBlockAssociation]
a} :: Subnet) 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 subnet.
subnet_ipv6Native :: Lens.Lens' Subnet (Prelude.Maybe Prelude.Bool)
subnet_ipv6Native :: Lens' Subnet (Maybe Bool)
subnet_ipv6Native = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subnet' {Maybe Bool
ipv6Native :: Maybe Bool
$sel:ipv6Native:Subnet' :: Subnet -> Maybe Bool
ipv6Native} -> Maybe Bool
ipv6Native) (\s :: Subnet
s@Subnet' {} Maybe Bool
a -> Subnet
s {$sel:ipv6Native:Subnet' :: Maybe Bool
ipv6Native = Maybe Bool
a} :: Subnet)

-- | Indicates whether a network interface created in this subnet (including
-- a network interface created by RunInstances) receives a customer-owned
-- IPv4 address.
subnet_mapCustomerOwnedIpOnLaunch :: Lens.Lens' Subnet (Prelude.Maybe Prelude.Bool)
subnet_mapCustomerOwnedIpOnLaunch :: Lens' Subnet (Maybe Bool)
subnet_mapCustomerOwnedIpOnLaunch = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subnet' {Maybe Bool
mapCustomerOwnedIpOnLaunch :: Maybe Bool
$sel:mapCustomerOwnedIpOnLaunch:Subnet' :: Subnet -> Maybe Bool
mapCustomerOwnedIpOnLaunch} -> Maybe Bool
mapCustomerOwnedIpOnLaunch) (\s :: Subnet
s@Subnet' {} Maybe Bool
a -> Subnet
s {$sel:mapCustomerOwnedIpOnLaunch:Subnet' :: Maybe Bool
mapCustomerOwnedIpOnLaunch = Maybe Bool
a} :: Subnet)

-- | Indicates whether instances launched in this subnet receive a public
-- IPv4 address.
subnet_mapPublicIpOnLaunch :: Lens.Lens' Subnet (Prelude.Maybe Prelude.Bool)
subnet_mapPublicIpOnLaunch :: Lens' Subnet (Maybe Bool)
subnet_mapPublicIpOnLaunch = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subnet' {Maybe Bool
mapPublicIpOnLaunch :: Maybe Bool
$sel:mapPublicIpOnLaunch:Subnet' :: Subnet -> Maybe Bool
mapPublicIpOnLaunch} -> Maybe Bool
mapPublicIpOnLaunch) (\s :: Subnet
s@Subnet' {} Maybe Bool
a -> Subnet
s {$sel:mapPublicIpOnLaunch:Subnet' :: Maybe Bool
mapPublicIpOnLaunch = Maybe Bool
a} :: Subnet)

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

-- | The ID of the Amazon Web Services account that owns the subnet.
subnet_ownerId :: Lens.Lens' Subnet (Prelude.Maybe Prelude.Text)
subnet_ownerId :: Lens' Subnet (Maybe Text)
subnet_ownerId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subnet' {Maybe Text
ownerId :: Maybe Text
$sel:ownerId:Subnet' :: Subnet -> Maybe Text
ownerId} -> Maybe Text
ownerId) (\s :: Subnet
s@Subnet' {} Maybe Text
a -> Subnet
s {$sel:ownerId:Subnet' :: Maybe Text
ownerId = Maybe Text
a} :: Subnet)

-- | The type of hostnames to assign to instances in the subnet at launch. An
-- instance hostname is based on the IPv4 address or ID of the instance.
subnet_privateDnsNameOptionsOnLaunch :: Lens.Lens' Subnet (Prelude.Maybe PrivateDnsNameOptionsOnLaunch)
subnet_privateDnsNameOptionsOnLaunch :: Lens' Subnet (Maybe PrivateDnsNameOptionsOnLaunch)
subnet_privateDnsNameOptionsOnLaunch = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subnet' {Maybe PrivateDnsNameOptionsOnLaunch
privateDnsNameOptionsOnLaunch :: Maybe PrivateDnsNameOptionsOnLaunch
$sel:privateDnsNameOptionsOnLaunch:Subnet' :: Subnet -> Maybe PrivateDnsNameOptionsOnLaunch
privateDnsNameOptionsOnLaunch} -> Maybe PrivateDnsNameOptionsOnLaunch
privateDnsNameOptionsOnLaunch) (\s :: Subnet
s@Subnet' {} Maybe PrivateDnsNameOptionsOnLaunch
a -> Subnet
s {$sel:privateDnsNameOptionsOnLaunch:Subnet' :: Maybe PrivateDnsNameOptionsOnLaunch
privateDnsNameOptionsOnLaunch = Maybe PrivateDnsNameOptionsOnLaunch
a} :: Subnet)

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

-- | Any tags assigned to the subnet.
subnet_tags :: Lens.Lens' Subnet (Prelude.Maybe [Tag])
subnet_tags :: Lens' Subnet (Maybe [Tag])
subnet_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subnet' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:Subnet' :: Subnet -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: Subnet
s@Subnet' {} Maybe [Tag]
a -> Subnet
s {$sel:tags:Subnet' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: Subnet) 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 Availability Zone of the subnet.
subnet_availabilityZone :: Lens.Lens' Subnet Prelude.Text
subnet_availabilityZone :: Lens' Subnet Text
subnet_availabilityZone = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subnet' {Text
availabilityZone :: Text
$sel:availabilityZone:Subnet' :: Subnet -> Text
availabilityZone} -> Text
availabilityZone) (\s :: Subnet
s@Subnet' {} Text
a -> Subnet
s {$sel:availabilityZone:Subnet' :: Text
availabilityZone = Text
a} :: Subnet)

-- | The number of unused private IPv4 addresses in the subnet. The IPv4
-- addresses for any stopped instances are considered unavailable.
subnet_availableIpAddressCount :: Lens.Lens' Subnet Prelude.Int
subnet_availableIpAddressCount :: Lens' Subnet Int
subnet_availableIpAddressCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subnet' {Int
availableIpAddressCount :: Int
$sel:availableIpAddressCount:Subnet' :: Subnet -> Int
availableIpAddressCount} -> Int
availableIpAddressCount) (\s :: Subnet
s@Subnet' {} Int
a -> Subnet
s {$sel:availableIpAddressCount:Subnet' :: Int
availableIpAddressCount = Int
a} :: Subnet)

-- | The IPv4 CIDR block assigned to the subnet.
subnet_cidrBlock :: Lens.Lens' Subnet Prelude.Text
subnet_cidrBlock :: Lens' Subnet Text
subnet_cidrBlock = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subnet' {Text
cidrBlock :: Text
$sel:cidrBlock:Subnet' :: Subnet -> Text
cidrBlock} -> Text
cidrBlock) (\s :: Subnet
s@Subnet' {} Text
a -> Subnet
s {$sel:cidrBlock:Subnet' :: Text
cidrBlock = Text
a} :: Subnet)

-- | The current state of the subnet.
subnet_state :: Lens.Lens' Subnet SubnetState
subnet_state :: Lens' Subnet SubnetState
subnet_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subnet' {SubnetState
state :: SubnetState
$sel:state:Subnet' :: Subnet -> SubnetState
state} -> SubnetState
state) (\s :: Subnet
s@Subnet' {} SubnetState
a -> Subnet
s {$sel:state:Subnet' :: SubnetState
state = SubnetState
a} :: Subnet)

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

-- | The ID of the VPC the subnet is in.
subnet_vpcId :: Lens.Lens' Subnet Prelude.Text
subnet_vpcId :: Lens' Subnet Text
subnet_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subnet' {Text
vpcId :: Text
$sel:vpcId:Subnet' :: Subnet -> Text
vpcId} -> Text
vpcId) (\s :: Subnet
s@Subnet' {} Text
a -> Subnet
s {$sel:vpcId:Subnet' :: Text
vpcId = Text
a} :: Subnet)

instance Data.FromXML Subnet where
  parseXML :: [Node] -> Either String Subnet
parseXML [Node]
x =
    Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe Bool
-> Maybe Int
-> Maybe [SubnetIpv6CidrBlockAssociation]
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe PrivateDnsNameOptionsOnLaunch
-> Maybe Text
-> Maybe [Tag]
-> Text
-> Int
-> Text
-> SubnetState
-> Text
-> Text
-> Subnet
Subnet'
      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
"assignIpv6AddressOnCreation")
      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
"availabilityZoneId")
      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
"customerOwnedIpv4Pool")
      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
"defaultForAz")
      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
"enableDns64")
      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
"enableLniAtDeviceIndex")
      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
"ipv6CidrBlockAssociationSet"
                      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
"mapCustomerOwnedIpOnLaunch")
      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
"mapPublicIpOnLaunch")
      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
"privateDnsNameOptionsOnLaunch")
      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
"subnetArn")
      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 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 a
Data..@ Text
"availableIpAddressCount")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"cidrBlock")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"state")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String 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 a
Data..@ Text
"vpcId")

instance Prelude.Hashable Subnet where
  hashWithSalt :: Int -> Subnet -> Int
hashWithSalt Int
_salt Subnet' {Int
Maybe Bool
Maybe Int
Maybe [SubnetIpv6CidrBlockAssociation]
Maybe [Tag]
Maybe Text
Maybe PrivateDnsNameOptionsOnLaunch
Text
SubnetState
vpcId :: Text
subnetId :: Text
state :: SubnetState
cidrBlock :: Text
availableIpAddressCount :: Int
availabilityZone :: Text
tags :: Maybe [Tag]
subnetArn :: Maybe Text
privateDnsNameOptionsOnLaunch :: Maybe PrivateDnsNameOptionsOnLaunch
ownerId :: Maybe Text
outpostArn :: Maybe Text
mapPublicIpOnLaunch :: Maybe Bool
mapCustomerOwnedIpOnLaunch :: Maybe Bool
ipv6Native :: Maybe Bool
ipv6CidrBlockAssociationSet :: Maybe [SubnetIpv6CidrBlockAssociation]
enableLniAtDeviceIndex :: Maybe Int
enableDns64 :: Maybe Bool
defaultForAz :: Maybe Bool
customerOwnedIpv4Pool :: Maybe Text
availabilityZoneId :: Maybe Text
assignIpv6AddressOnCreation :: Maybe Bool
$sel:vpcId:Subnet' :: Subnet -> Text
$sel:subnetId:Subnet' :: Subnet -> Text
$sel:state:Subnet' :: Subnet -> SubnetState
$sel:cidrBlock:Subnet' :: Subnet -> Text
$sel:availableIpAddressCount:Subnet' :: Subnet -> Int
$sel:availabilityZone:Subnet' :: Subnet -> Text
$sel:tags:Subnet' :: Subnet -> Maybe [Tag]
$sel:subnetArn:Subnet' :: Subnet -> Maybe Text
$sel:privateDnsNameOptionsOnLaunch:Subnet' :: Subnet -> Maybe PrivateDnsNameOptionsOnLaunch
$sel:ownerId:Subnet' :: Subnet -> Maybe Text
$sel:outpostArn:Subnet' :: Subnet -> Maybe Text
$sel:mapPublicIpOnLaunch:Subnet' :: Subnet -> Maybe Bool
$sel:mapCustomerOwnedIpOnLaunch:Subnet' :: Subnet -> Maybe Bool
$sel:ipv6Native:Subnet' :: Subnet -> Maybe Bool
$sel:ipv6CidrBlockAssociationSet:Subnet' :: Subnet -> Maybe [SubnetIpv6CidrBlockAssociation]
$sel:enableLniAtDeviceIndex:Subnet' :: Subnet -> Maybe Int
$sel:enableDns64:Subnet' :: Subnet -> Maybe Bool
$sel:defaultForAz:Subnet' :: Subnet -> Maybe Bool
$sel:customerOwnedIpv4Pool:Subnet' :: Subnet -> Maybe Text
$sel:availabilityZoneId:Subnet' :: Subnet -> Maybe Text
$sel:assignIpv6AddressOnCreation:Subnet' :: Subnet -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
assignIpv6AddressOnCreation
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
availabilityZoneId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
customerOwnedIpv4Pool
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
defaultForAz
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
enableDns64
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
enableLniAtDeviceIndex
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [SubnetIpv6CidrBlockAssociation]
ipv6CidrBlockAssociationSet
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
ipv6Native
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
mapCustomerOwnedIpOnLaunch
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
mapPublicIpOnLaunch
      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 PrivateDnsNameOptionsOnLaunch
privateDnsNameOptionsOnLaunch
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
subnetArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
availabilityZone
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Int
availableIpAddressCount
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
cidrBlock
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` SubnetState
state
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
subnetId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
vpcId

instance Prelude.NFData Subnet where
  rnf :: Subnet -> ()
rnf Subnet' {Int
Maybe Bool
Maybe Int
Maybe [SubnetIpv6CidrBlockAssociation]
Maybe [Tag]
Maybe Text
Maybe PrivateDnsNameOptionsOnLaunch
Text
SubnetState
vpcId :: Text
subnetId :: Text
state :: SubnetState
cidrBlock :: Text
availableIpAddressCount :: Int
availabilityZone :: Text
tags :: Maybe [Tag]
subnetArn :: Maybe Text
privateDnsNameOptionsOnLaunch :: Maybe PrivateDnsNameOptionsOnLaunch
ownerId :: Maybe Text
outpostArn :: Maybe Text
mapPublicIpOnLaunch :: Maybe Bool
mapCustomerOwnedIpOnLaunch :: Maybe Bool
ipv6Native :: Maybe Bool
ipv6CidrBlockAssociationSet :: Maybe [SubnetIpv6CidrBlockAssociation]
enableLniAtDeviceIndex :: Maybe Int
enableDns64 :: Maybe Bool
defaultForAz :: Maybe Bool
customerOwnedIpv4Pool :: Maybe Text
availabilityZoneId :: Maybe Text
assignIpv6AddressOnCreation :: Maybe Bool
$sel:vpcId:Subnet' :: Subnet -> Text
$sel:subnetId:Subnet' :: Subnet -> Text
$sel:state:Subnet' :: Subnet -> SubnetState
$sel:cidrBlock:Subnet' :: Subnet -> Text
$sel:availableIpAddressCount:Subnet' :: Subnet -> Int
$sel:availabilityZone:Subnet' :: Subnet -> Text
$sel:tags:Subnet' :: Subnet -> Maybe [Tag]
$sel:subnetArn:Subnet' :: Subnet -> Maybe Text
$sel:privateDnsNameOptionsOnLaunch:Subnet' :: Subnet -> Maybe PrivateDnsNameOptionsOnLaunch
$sel:ownerId:Subnet' :: Subnet -> Maybe Text
$sel:outpostArn:Subnet' :: Subnet -> Maybe Text
$sel:mapPublicIpOnLaunch:Subnet' :: Subnet -> Maybe Bool
$sel:mapCustomerOwnedIpOnLaunch:Subnet' :: Subnet -> Maybe Bool
$sel:ipv6Native:Subnet' :: Subnet -> Maybe Bool
$sel:ipv6CidrBlockAssociationSet:Subnet' :: Subnet -> Maybe [SubnetIpv6CidrBlockAssociation]
$sel:enableLniAtDeviceIndex:Subnet' :: Subnet -> Maybe Int
$sel:enableDns64:Subnet' :: Subnet -> Maybe Bool
$sel:defaultForAz:Subnet' :: Subnet -> Maybe Bool
$sel:customerOwnedIpv4Pool:Subnet' :: Subnet -> Maybe Text
$sel:availabilityZoneId:Subnet' :: Subnet -> Maybe Text
$sel:assignIpv6AddressOnCreation:Subnet' :: Subnet -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
assignIpv6AddressOnCreation
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
availabilityZoneId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
customerOwnedIpv4Pool
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
defaultForAz
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
enableDns64
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
enableLniAtDeviceIndex
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [SubnetIpv6CidrBlockAssociation]
ipv6CidrBlockAssociationSet
      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 Bool
mapCustomerOwnedIpOnLaunch
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
mapPublicIpOnLaunch
      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 PrivateDnsNameOptionsOnLaunch
privateDnsNameOptionsOnLaunch
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
subnetArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
availabilityZone
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
availableIpAddressCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
cidrBlock
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf SubnetState
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
subnetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
vpcId