{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# 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.ModifySubnetAttribute
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Modifies a subnet attribute. You can only modify one attribute at a
-- time.
--
-- Use this action to modify subnets on Amazon Web Services Outposts.
--
-- -   To modify a subnet on an Outpost rack, set both
--     @MapCustomerOwnedIpOnLaunch@ and @CustomerOwnedIpv4Pool@. These two
--     parameters act as a single attribute.
--
-- -   To modify a subnet on an Outpost server, set either
--     @EnableLniAtDeviceIndex@ or @DisableLniAtDeviceIndex@.
--
-- For more information about Amazon Web Services Outposts, see the
-- following:
--
-- -   <https://docs.aws.amazon.com/outposts/latest/userguide/how-servers-work.html Outpost servers>
--
-- -   <https://docs.aws.amazon.com/outposts/latest/userguide/how-racks-work.html Outpost racks>
module Amazonka.EC2.ModifySubnetAttribute
  ( -- * Creating a Request
    ModifySubnetAttribute (..),
    newModifySubnetAttribute,

    -- * Request Lenses
    modifySubnetAttribute_assignIpv6AddressOnCreation,
    modifySubnetAttribute_customerOwnedIpv4Pool,
    modifySubnetAttribute_disableLniAtDeviceIndex,
    modifySubnetAttribute_enableDns64,
    modifySubnetAttribute_enableLniAtDeviceIndex,
    modifySubnetAttribute_enableResourceNameDnsAAAARecordOnLaunch,
    modifySubnetAttribute_enableResourceNameDnsARecordOnLaunch,
    modifySubnetAttribute_mapCustomerOwnedIpOnLaunch,
    modifySubnetAttribute_mapPublicIpOnLaunch,
    modifySubnetAttribute_privateDnsHostnameTypeOnLaunch,
    modifySubnetAttribute_subnetId,

    -- * Destructuring the Response
    ModifySubnetAttributeResponse (..),
    newModifySubnetAttributeResponse,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EC2.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newModifySubnetAttribute' smart constructor.
data ModifySubnetAttribute = ModifySubnetAttribute'
  { -- | Specify @true@ to indicate that network interfaces created in the
    -- specified subnet should be assigned an IPv6 address. This includes a
    -- network interface that\'s created when launching an instance into the
    -- subnet (the instance therefore receives an IPv6 address).
    --
    -- If you enable the IPv6 addressing feature for your subnet, your network
    -- interface or instance only receives an IPv6 address if it\'s created
    -- using version @2016-11-15@ or later of the Amazon EC2 API.
    ModifySubnetAttribute -> Maybe AttributeBooleanValue
assignIpv6AddressOnCreation :: Prelude.Maybe AttributeBooleanValue,
    -- | The customer-owned IPv4 address pool associated with the subnet.
    --
    -- You must set this value when you specify @true@ for
    -- @MapCustomerOwnedIpOnLaunch@.
    ModifySubnetAttribute -> Maybe Text
customerOwnedIpv4Pool :: Prelude.Maybe Prelude.Text,
    -- | Specify @true@ to indicate that local network interfaces at the current
    -- position should be disabled.
    ModifySubnetAttribute -> Maybe AttributeBooleanValue
disableLniAtDeviceIndex :: Prelude.Maybe AttributeBooleanValue,
    -- | Indicates whether DNS queries made to the Amazon-provided DNS Resolver
    -- in this subnet should return synthetic IPv6 addresses for IPv4-only
    -- destinations.
    ModifySubnetAttribute -> Maybe AttributeBooleanValue
enableDns64 :: Prelude.Maybe AttributeBooleanValue,
    -- | 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). A local network
    -- interface cannot be the primary network interface (eth0).
    ModifySubnetAttribute -> Maybe Int
enableLniAtDeviceIndex :: Prelude.Maybe Prelude.Int,
    -- | Indicates whether to respond to DNS queries for instance hostnames with
    -- DNS AAAA records.
    ModifySubnetAttribute -> Maybe AttributeBooleanValue
enableResourceNameDnsAAAARecordOnLaunch :: Prelude.Maybe AttributeBooleanValue,
    -- | Indicates whether to respond to DNS queries for instance hostnames with
    -- DNS A records.
    ModifySubnetAttribute -> Maybe AttributeBooleanValue
enableResourceNameDnsARecordOnLaunch :: Prelude.Maybe AttributeBooleanValue,
    -- | Specify @true@ to indicate that network interfaces attached to instances
    -- created in the specified subnet should be assigned a customer-owned IPv4
    -- address.
    --
    -- When this value is @true@, you must specify the customer-owned IP pool
    -- using @CustomerOwnedIpv4Pool@.
    ModifySubnetAttribute -> Maybe AttributeBooleanValue
mapCustomerOwnedIpOnLaunch :: Prelude.Maybe AttributeBooleanValue,
    -- | Specify @true@ to indicate that network interfaces attached to instances
    -- created in the specified subnet should be assigned a public IPv4
    -- address.
    ModifySubnetAttribute -> Maybe AttributeBooleanValue
mapPublicIpOnLaunch :: Prelude.Maybe AttributeBooleanValue,
    -- | The type of hostname to assign to instances in the subnet at launch. For
    -- IPv4-only and dual-stack (IPv4 and IPv6) subnets, an instance DNS name
    -- can be based on the instance IPv4 address (ip-name) or the instance ID
    -- (resource-name). For IPv6 only subnets, an instance DNS name must be
    -- based on the instance ID (resource-name).
    ModifySubnetAttribute -> Maybe HostnameType
privateDnsHostnameTypeOnLaunch :: Prelude.Maybe HostnameType,
    -- | The ID of the subnet.
    ModifySubnetAttribute -> Text
subnetId :: Prelude.Text
  }
  deriving (ModifySubnetAttribute -> ModifySubnetAttribute -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModifySubnetAttribute -> ModifySubnetAttribute -> Bool
$c/= :: ModifySubnetAttribute -> ModifySubnetAttribute -> Bool
== :: ModifySubnetAttribute -> ModifySubnetAttribute -> Bool
$c== :: ModifySubnetAttribute -> ModifySubnetAttribute -> Bool
Prelude.Eq, ReadPrec [ModifySubnetAttribute]
ReadPrec ModifySubnetAttribute
Int -> ReadS ModifySubnetAttribute
ReadS [ModifySubnetAttribute]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModifySubnetAttribute]
$creadListPrec :: ReadPrec [ModifySubnetAttribute]
readPrec :: ReadPrec ModifySubnetAttribute
$creadPrec :: ReadPrec ModifySubnetAttribute
readList :: ReadS [ModifySubnetAttribute]
$creadList :: ReadS [ModifySubnetAttribute]
readsPrec :: Int -> ReadS ModifySubnetAttribute
$creadsPrec :: Int -> ReadS ModifySubnetAttribute
Prelude.Read, Int -> ModifySubnetAttribute -> ShowS
[ModifySubnetAttribute] -> ShowS
ModifySubnetAttribute -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModifySubnetAttribute] -> ShowS
$cshowList :: [ModifySubnetAttribute] -> ShowS
show :: ModifySubnetAttribute -> String
$cshow :: ModifySubnetAttribute -> String
showsPrec :: Int -> ModifySubnetAttribute -> ShowS
$cshowsPrec :: Int -> ModifySubnetAttribute -> ShowS
Prelude.Show, forall x. Rep ModifySubnetAttribute x -> ModifySubnetAttribute
forall x. ModifySubnetAttribute -> Rep ModifySubnetAttribute x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ModifySubnetAttribute x -> ModifySubnetAttribute
$cfrom :: forall x. ModifySubnetAttribute -> Rep ModifySubnetAttribute x
Prelude.Generic)

-- |
-- Create a value of 'ModifySubnetAttribute' 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', 'modifySubnetAttribute_assignIpv6AddressOnCreation' - Specify @true@ to indicate that network interfaces created in the
-- specified subnet should be assigned an IPv6 address. This includes a
-- network interface that\'s created when launching an instance into the
-- subnet (the instance therefore receives an IPv6 address).
--
-- If you enable the IPv6 addressing feature for your subnet, your network
-- interface or instance only receives an IPv6 address if it\'s created
-- using version @2016-11-15@ or later of the Amazon EC2 API.
--
-- 'customerOwnedIpv4Pool', 'modifySubnetAttribute_customerOwnedIpv4Pool' - The customer-owned IPv4 address pool associated with the subnet.
--
-- You must set this value when you specify @true@ for
-- @MapCustomerOwnedIpOnLaunch@.
--
-- 'disableLniAtDeviceIndex', 'modifySubnetAttribute_disableLniAtDeviceIndex' - Specify @true@ to indicate that local network interfaces at the current
-- position should be disabled.
--
-- 'enableDns64', 'modifySubnetAttribute_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', 'modifySubnetAttribute_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). A local network
-- interface cannot be the primary network interface (eth0).
--
-- 'enableResourceNameDnsAAAARecordOnLaunch', 'modifySubnetAttribute_enableResourceNameDnsAAAARecordOnLaunch' - Indicates whether to respond to DNS queries for instance hostnames with
-- DNS AAAA records.
--
-- 'enableResourceNameDnsARecordOnLaunch', 'modifySubnetAttribute_enableResourceNameDnsARecordOnLaunch' - Indicates whether to respond to DNS queries for instance hostnames with
-- DNS A records.
--
-- 'mapCustomerOwnedIpOnLaunch', 'modifySubnetAttribute_mapCustomerOwnedIpOnLaunch' - Specify @true@ to indicate that network interfaces attached to instances
-- created in the specified subnet should be assigned a customer-owned IPv4
-- address.
--
-- When this value is @true@, you must specify the customer-owned IP pool
-- using @CustomerOwnedIpv4Pool@.
--
-- 'mapPublicIpOnLaunch', 'modifySubnetAttribute_mapPublicIpOnLaunch' - Specify @true@ to indicate that network interfaces attached to instances
-- created in the specified subnet should be assigned a public IPv4
-- address.
--
-- 'privateDnsHostnameTypeOnLaunch', 'modifySubnetAttribute_privateDnsHostnameTypeOnLaunch' - The type of hostname to assign to instances in the subnet at launch. For
-- IPv4-only and dual-stack (IPv4 and IPv6) subnets, an instance DNS name
-- can be based on the instance IPv4 address (ip-name) or the instance ID
-- (resource-name). For IPv6 only subnets, an instance DNS name must be
-- based on the instance ID (resource-name).
--
-- 'subnetId', 'modifySubnetAttribute_subnetId' - The ID of the subnet.
newModifySubnetAttribute ::
  -- | 'subnetId'
  Prelude.Text ->
  ModifySubnetAttribute
newModifySubnetAttribute :: Text -> ModifySubnetAttribute
newModifySubnetAttribute Text
pSubnetId_ =
  ModifySubnetAttribute'
    { $sel:assignIpv6AddressOnCreation:ModifySubnetAttribute' :: Maybe AttributeBooleanValue
assignIpv6AddressOnCreation =
        forall a. Maybe a
Prelude.Nothing,
      $sel:customerOwnedIpv4Pool:ModifySubnetAttribute' :: Maybe Text
customerOwnedIpv4Pool = forall a. Maybe a
Prelude.Nothing,
      $sel:disableLniAtDeviceIndex:ModifySubnetAttribute' :: Maybe AttributeBooleanValue
disableLniAtDeviceIndex = forall a. Maybe a
Prelude.Nothing,
      $sel:enableDns64:ModifySubnetAttribute' :: Maybe AttributeBooleanValue
enableDns64 = forall a. Maybe a
Prelude.Nothing,
      $sel:enableLniAtDeviceIndex:ModifySubnetAttribute' :: Maybe Int
enableLniAtDeviceIndex = forall a. Maybe a
Prelude.Nothing,
      $sel:enableResourceNameDnsAAAARecordOnLaunch:ModifySubnetAttribute' :: Maybe AttributeBooleanValue
enableResourceNameDnsAAAARecordOnLaunch =
        forall a. Maybe a
Prelude.Nothing,
      $sel:enableResourceNameDnsARecordOnLaunch:ModifySubnetAttribute' :: Maybe AttributeBooleanValue
enableResourceNameDnsARecordOnLaunch =
        forall a. Maybe a
Prelude.Nothing,
      $sel:mapCustomerOwnedIpOnLaunch:ModifySubnetAttribute' :: Maybe AttributeBooleanValue
mapCustomerOwnedIpOnLaunch = forall a. Maybe a
Prelude.Nothing,
      $sel:mapPublicIpOnLaunch:ModifySubnetAttribute' :: Maybe AttributeBooleanValue
mapPublicIpOnLaunch = forall a. Maybe a
Prelude.Nothing,
      $sel:privateDnsHostnameTypeOnLaunch:ModifySubnetAttribute' :: Maybe HostnameType
privateDnsHostnameTypeOnLaunch = forall a. Maybe a
Prelude.Nothing,
      $sel:subnetId:ModifySubnetAttribute' :: Text
subnetId = Text
pSubnetId_
    }

-- | Specify @true@ to indicate that network interfaces created in the
-- specified subnet should be assigned an IPv6 address. This includes a
-- network interface that\'s created when launching an instance into the
-- subnet (the instance therefore receives an IPv6 address).
--
-- If you enable the IPv6 addressing feature for your subnet, your network
-- interface or instance only receives an IPv6 address if it\'s created
-- using version @2016-11-15@ or later of the Amazon EC2 API.
modifySubnetAttribute_assignIpv6AddressOnCreation :: Lens.Lens' ModifySubnetAttribute (Prelude.Maybe AttributeBooleanValue)
modifySubnetAttribute_assignIpv6AddressOnCreation :: Lens' ModifySubnetAttribute (Maybe AttributeBooleanValue)
modifySubnetAttribute_assignIpv6AddressOnCreation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifySubnetAttribute' {Maybe AttributeBooleanValue
assignIpv6AddressOnCreation :: Maybe AttributeBooleanValue
$sel:assignIpv6AddressOnCreation:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
assignIpv6AddressOnCreation} -> Maybe AttributeBooleanValue
assignIpv6AddressOnCreation) (\s :: ModifySubnetAttribute
s@ModifySubnetAttribute' {} Maybe AttributeBooleanValue
a -> ModifySubnetAttribute
s {$sel:assignIpv6AddressOnCreation:ModifySubnetAttribute' :: Maybe AttributeBooleanValue
assignIpv6AddressOnCreation = Maybe AttributeBooleanValue
a} :: ModifySubnetAttribute)

-- | The customer-owned IPv4 address pool associated with the subnet.
--
-- You must set this value when you specify @true@ for
-- @MapCustomerOwnedIpOnLaunch@.
modifySubnetAttribute_customerOwnedIpv4Pool :: Lens.Lens' ModifySubnetAttribute (Prelude.Maybe Prelude.Text)
modifySubnetAttribute_customerOwnedIpv4Pool :: Lens' ModifySubnetAttribute (Maybe Text)
modifySubnetAttribute_customerOwnedIpv4Pool = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifySubnetAttribute' {Maybe Text
customerOwnedIpv4Pool :: Maybe Text
$sel:customerOwnedIpv4Pool:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe Text
customerOwnedIpv4Pool} -> Maybe Text
customerOwnedIpv4Pool) (\s :: ModifySubnetAttribute
s@ModifySubnetAttribute' {} Maybe Text
a -> ModifySubnetAttribute
s {$sel:customerOwnedIpv4Pool:ModifySubnetAttribute' :: Maybe Text
customerOwnedIpv4Pool = Maybe Text
a} :: ModifySubnetAttribute)

-- | Specify @true@ to indicate that local network interfaces at the current
-- position should be disabled.
modifySubnetAttribute_disableLniAtDeviceIndex :: Lens.Lens' ModifySubnetAttribute (Prelude.Maybe AttributeBooleanValue)
modifySubnetAttribute_disableLniAtDeviceIndex :: Lens' ModifySubnetAttribute (Maybe AttributeBooleanValue)
modifySubnetAttribute_disableLniAtDeviceIndex = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifySubnetAttribute' {Maybe AttributeBooleanValue
disableLniAtDeviceIndex :: Maybe AttributeBooleanValue
$sel:disableLniAtDeviceIndex:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
disableLniAtDeviceIndex} -> Maybe AttributeBooleanValue
disableLniAtDeviceIndex) (\s :: ModifySubnetAttribute
s@ModifySubnetAttribute' {} Maybe AttributeBooleanValue
a -> ModifySubnetAttribute
s {$sel:disableLniAtDeviceIndex:ModifySubnetAttribute' :: Maybe AttributeBooleanValue
disableLniAtDeviceIndex = Maybe AttributeBooleanValue
a} :: ModifySubnetAttribute)

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

-- | 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). A local network
-- interface cannot be the primary network interface (eth0).
modifySubnetAttribute_enableLniAtDeviceIndex :: Lens.Lens' ModifySubnetAttribute (Prelude.Maybe Prelude.Int)
modifySubnetAttribute_enableLniAtDeviceIndex :: Lens' ModifySubnetAttribute (Maybe Int)
modifySubnetAttribute_enableLniAtDeviceIndex = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifySubnetAttribute' {Maybe Int
enableLniAtDeviceIndex :: Maybe Int
$sel:enableLniAtDeviceIndex:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe Int
enableLniAtDeviceIndex} -> Maybe Int
enableLniAtDeviceIndex) (\s :: ModifySubnetAttribute
s@ModifySubnetAttribute' {} Maybe Int
a -> ModifySubnetAttribute
s {$sel:enableLniAtDeviceIndex:ModifySubnetAttribute' :: Maybe Int
enableLniAtDeviceIndex = Maybe Int
a} :: ModifySubnetAttribute)

-- | Indicates whether to respond to DNS queries for instance hostnames with
-- DNS AAAA records.
modifySubnetAttribute_enableResourceNameDnsAAAARecordOnLaunch :: Lens.Lens' ModifySubnetAttribute (Prelude.Maybe AttributeBooleanValue)
modifySubnetAttribute_enableResourceNameDnsAAAARecordOnLaunch :: Lens' ModifySubnetAttribute (Maybe AttributeBooleanValue)
modifySubnetAttribute_enableResourceNameDnsAAAARecordOnLaunch = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifySubnetAttribute' {Maybe AttributeBooleanValue
enableResourceNameDnsAAAARecordOnLaunch :: Maybe AttributeBooleanValue
$sel:enableResourceNameDnsAAAARecordOnLaunch:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
enableResourceNameDnsAAAARecordOnLaunch} -> Maybe AttributeBooleanValue
enableResourceNameDnsAAAARecordOnLaunch) (\s :: ModifySubnetAttribute
s@ModifySubnetAttribute' {} Maybe AttributeBooleanValue
a -> ModifySubnetAttribute
s {$sel:enableResourceNameDnsAAAARecordOnLaunch:ModifySubnetAttribute' :: Maybe AttributeBooleanValue
enableResourceNameDnsAAAARecordOnLaunch = Maybe AttributeBooleanValue
a} :: ModifySubnetAttribute)

-- | Indicates whether to respond to DNS queries for instance hostnames with
-- DNS A records.
modifySubnetAttribute_enableResourceNameDnsARecordOnLaunch :: Lens.Lens' ModifySubnetAttribute (Prelude.Maybe AttributeBooleanValue)
modifySubnetAttribute_enableResourceNameDnsARecordOnLaunch :: Lens' ModifySubnetAttribute (Maybe AttributeBooleanValue)
modifySubnetAttribute_enableResourceNameDnsARecordOnLaunch = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifySubnetAttribute' {Maybe AttributeBooleanValue
enableResourceNameDnsARecordOnLaunch :: Maybe AttributeBooleanValue
$sel:enableResourceNameDnsARecordOnLaunch:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
enableResourceNameDnsARecordOnLaunch} -> Maybe AttributeBooleanValue
enableResourceNameDnsARecordOnLaunch) (\s :: ModifySubnetAttribute
s@ModifySubnetAttribute' {} Maybe AttributeBooleanValue
a -> ModifySubnetAttribute
s {$sel:enableResourceNameDnsARecordOnLaunch:ModifySubnetAttribute' :: Maybe AttributeBooleanValue
enableResourceNameDnsARecordOnLaunch = Maybe AttributeBooleanValue
a} :: ModifySubnetAttribute)

-- | Specify @true@ to indicate that network interfaces attached to instances
-- created in the specified subnet should be assigned a customer-owned IPv4
-- address.
--
-- When this value is @true@, you must specify the customer-owned IP pool
-- using @CustomerOwnedIpv4Pool@.
modifySubnetAttribute_mapCustomerOwnedIpOnLaunch :: Lens.Lens' ModifySubnetAttribute (Prelude.Maybe AttributeBooleanValue)
modifySubnetAttribute_mapCustomerOwnedIpOnLaunch :: Lens' ModifySubnetAttribute (Maybe AttributeBooleanValue)
modifySubnetAttribute_mapCustomerOwnedIpOnLaunch = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifySubnetAttribute' {Maybe AttributeBooleanValue
mapCustomerOwnedIpOnLaunch :: Maybe AttributeBooleanValue
$sel:mapCustomerOwnedIpOnLaunch:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
mapCustomerOwnedIpOnLaunch} -> Maybe AttributeBooleanValue
mapCustomerOwnedIpOnLaunch) (\s :: ModifySubnetAttribute
s@ModifySubnetAttribute' {} Maybe AttributeBooleanValue
a -> ModifySubnetAttribute
s {$sel:mapCustomerOwnedIpOnLaunch:ModifySubnetAttribute' :: Maybe AttributeBooleanValue
mapCustomerOwnedIpOnLaunch = Maybe AttributeBooleanValue
a} :: ModifySubnetAttribute)

-- | Specify @true@ to indicate that network interfaces attached to instances
-- created in the specified subnet should be assigned a public IPv4
-- address.
modifySubnetAttribute_mapPublicIpOnLaunch :: Lens.Lens' ModifySubnetAttribute (Prelude.Maybe AttributeBooleanValue)
modifySubnetAttribute_mapPublicIpOnLaunch :: Lens' ModifySubnetAttribute (Maybe AttributeBooleanValue)
modifySubnetAttribute_mapPublicIpOnLaunch = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifySubnetAttribute' {Maybe AttributeBooleanValue
mapPublicIpOnLaunch :: Maybe AttributeBooleanValue
$sel:mapPublicIpOnLaunch:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
mapPublicIpOnLaunch} -> Maybe AttributeBooleanValue
mapPublicIpOnLaunch) (\s :: ModifySubnetAttribute
s@ModifySubnetAttribute' {} Maybe AttributeBooleanValue
a -> ModifySubnetAttribute
s {$sel:mapPublicIpOnLaunch:ModifySubnetAttribute' :: Maybe AttributeBooleanValue
mapPublicIpOnLaunch = Maybe AttributeBooleanValue
a} :: ModifySubnetAttribute)

-- | The type of hostname to assign to instances in the subnet at launch. For
-- IPv4-only and dual-stack (IPv4 and IPv6) subnets, an instance DNS name
-- can be based on the instance IPv4 address (ip-name) or the instance ID
-- (resource-name). For IPv6 only subnets, an instance DNS name must be
-- based on the instance ID (resource-name).
modifySubnetAttribute_privateDnsHostnameTypeOnLaunch :: Lens.Lens' ModifySubnetAttribute (Prelude.Maybe HostnameType)
modifySubnetAttribute_privateDnsHostnameTypeOnLaunch :: Lens' ModifySubnetAttribute (Maybe HostnameType)
modifySubnetAttribute_privateDnsHostnameTypeOnLaunch = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifySubnetAttribute' {Maybe HostnameType
privateDnsHostnameTypeOnLaunch :: Maybe HostnameType
$sel:privateDnsHostnameTypeOnLaunch:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe HostnameType
privateDnsHostnameTypeOnLaunch} -> Maybe HostnameType
privateDnsHostnameTypeOnLaunch) (\s :: ModifySubnetAttribute
s@ModifySubnetAttribute' {} Maybe HostnameType
a -> ModifySubnetAttribute
s {$sel:privateDnsHostnameTypeOnLaunch:ModifySubnetAttribute' :: Maybe HostnameType
privateDnsHostnameTypeOnLaunch = Maybe HostnameType
a} :: ModifySubnetAttribute)

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

instance Core.AWSRequest ModifySubnetAttribute where
  type
    AWSResponse ModifySubnetAttribute =
      ModifySubnetAttributeResponse
  request :: (Service -> Service)
-> ModifySubnetAttribute -> Request ModifySubnetAttribute
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ModifySubnetAttribute
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ModifySubnetAttribute)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull ModifySubnetAttributeResponse
ModifySubnetAttributeResponse'

instance Prelude.Hashable ModifySubnetAttribute where
  hashWithSalt :: Int -> ModifySubnetAttribute -> Int
hashWithSalt Int
_salt ModifySubnetAttribute' {Maybe Int
Maybe Text
Maybe AttributeBooleanValue
Maybe HostnameType
Text
subnetId :: Text
privateDnsHostnameTypeOnLaunch :: Maybe HostnameType
mapPublicIpOnLaunch :: Maybe AttributeBooleanValue
mapCustomerOwnedIpOnLaunch :: Maybe AttributeBooleanValue
enableResourceNameDnsARecordOnLaunch :: Maybe AttributeBooleanValue
enableResourceNameDnsAAAARecordOnLaunch :: Maybe AttributeBooleanValue
enableLniAtDeviceIndex :: Maybe Int
enableDns64 :: Maybe AttributeBooleanValue
disableLniAtDeviceIndex :: Maybe AttributeBooleanValue
customerOwnedIpv4Pool :: Maybe Text
assignIpv6AddressOnCreation :: Maybe AttributeBooleanValue
$sel:subnetId:ModifySubnetAttribute' :: ModifySubnetAttribute -> Text
$sel:privateDnsHostnameTypeOnLaunch:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe HostnameType
$sel:mapPublicIpOnLaunch:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
$sel:mapCustomerOwnedIpOnLaunch:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
$sel:enableResourceNameDnsARecordOnLaunch:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
$sel:enableResourceNameDnsAAAARecordOnLaunch:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
$sel:enableLniAtDeviceIndex:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe Int
$sel:enableDns64:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
$sel:disableLniAtDeviceIndex:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
$sel:customerOwnedIpv4Pool:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe Text
$sel:assignIpv6AddressOnCreation:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AttributeBooleanValue
assignIpv6AddressOnCreation
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
customerOwnedIpv4Pool
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AttributeBooleanValue
disableLniAtDeviceIndex
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AttributeBooleanValue
enableDns64
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
enableLniAtDeviceIndex
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AttributeBooleanValue
enableResourceNameDnsAAAARecordOnLaunch
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AttributeBooleanValue
enableResourceNameDnsARecordOnLaunch
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AttributeBooleanValue
mapCustomerOwnedIpOnLaunch
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AttributeBooleanValue
mapPublicIpOnLaunch
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HostnameType
privateDnsHostnameTypeOnLaunch
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
subnetId

instance Prelude.NFData ModifySubnetAttribute where
  rnf :: ModifySubnetAttribute -> ()
rnf ModifySubnetAttribute' {Maybe Int
Maybe Text
Maybe AttributeBooleanValue
Maybe HostnameType
Text
subnetId :: Text
privateDnsHostnameTypeOnLaunch :: Maybe HostnameType
mapPublicIpOnLaunch :: Maybe AttributeBooleanValue
mapCustomerOwnedIpOnLaunch :: Maybe AttributeBooleanValue
enableResourceNameDnsARecordOnLaunch :: Maybe AttributeBooleanValue
enableResourceNameDnsAAAARecordOnLaunch :: Maybe AttributeBooleanValue
enableLniAtDeviceIndex :: Maybe Int
enableDns64 :: Maybe AttributeBooleanValue
disableLniAtDeviceIndex :: Maybe AttributeBooleanValue
customerOwnedIpv4Pool :: Maybe Text
assignIpv6AddressOnCreation :: Maybe AttributeBooleanValue
$sel:subnetId:ModifySubnetAttribute' :: ModifySubnetAttribute -> Text
$sel:privateDnsHostnameTypeOnLaunch:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe HostnameType
$sel:mapPublicIpOnLaunch:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
$sel:mapCustomerOwnedIpOnLaunch:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
$sel:enableResourceNameDnsARecordOnLaunch:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
$sel:enableResourceNameDnsAAAARecordOnLaunch:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
$sel:enableLniAtDeviceIndex:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe Int
$sel:enableDns64:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
$sel:disableLniAtDeviceIndex:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
$sel:customerOwnedIpv4Pool:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe Text
$sel:assignIpv6AddressOnCreation:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AttributeBooleanValue
assignIpv6AddressOnCreation
      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 AttributeBooleanValue
disableLniAtDeviceIndex
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AttributeBooleanValue
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 AttributeBooleanValue
enableResourceNameDnsAAAARecordOnLaunch
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AttributeBooleanValue
enableResourceNameDnsARecordOnLaunch
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AttributeBooleanValue
mapCustomerOwnedIpOnLaunch
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AttributeBooleanValue
mapPublicIpOnLaunch
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HostnameType
privateDnsHostnameTypeOnLaunch
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
subnetId

instance Data.ToHeaders ModifySubnetAttribute where
  toHeaders :: ModifySubnetAttribute -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath ModifySubnetAttribute where
  toPath :: ModifySubnetAttribute -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery ModifySubnetAttribute where
  toQuery :: ModifySubnetAttribute -> QueryString
toQuery ModifySubnetAttribute' {Maybe Int
Maybe Text
Maybe AttributeBooleanValue
Maybe HostnameType
Text
subnetId :: Text
privateDnsHostnameTypeOnLaunch :: Maybe HostnameType
mapPublicIpOnLaunch :: Maybe AttributeBooleanValue
mapCustomerOwnedIpOnLaunch :: Maybe AttributeBooleanValue
enableResourceNameDnsARecordOnLaunch :: Maybe AttributeBooleanValue
enableResourceNameDnsAAAARecordOnLaunch :: Maybe AttributeBooleanValue
enableLniAtDeviceIndex :: Maybe Int
enableDns64 :: Maybe AttributeBooleanValue
disableLniAtDeviceIndex :: Maybe AttributeBooleanValue
customerOwnedIpv4Pool :: Maybe Text
assignIpv6AddressOnCreation :: Maybe AttributeBooleanValue
$sel:subnetId:ModifySubnetAttribute' :: ModifySubnetAttribute -> Text
$sel:privateDnsHostnameTypeOnLaunch:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe HostnameType
$sel:mapPublicIpOnLaunch:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
$sel:mapCustomerOwnedIpOnLaunch:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
$sel:enableResourceNameDnsARecordOnLaunch:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
$sel:enableResourceNameDnsAAAARecordOnLaunch:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
$sel:enableLniAtDeviceIndex:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe Int
$sel:enableDns64:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
$sel:disableLniAtDeviceIndex:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
$sel:customerOwnedIpv4Pool:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe Text
$sel:assignIpv6AddressOnCreation:ModifySubnetAttribute' :: ModifySubnetAttribute -> Maybe AttributeBooleanValue
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"ModifySubnetAttribute" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"AssignIpv6AddressOnCreation"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe AttributeBooleanValue
assignIpv6AddressOnCreation,
        ByteString
"CustomerOwnedIpv4Pool"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
customerOwnedIpv4Pool,
        ByteString
"DisableLniAtDeviceIndex"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe AttributeBooleanValue
disableLniAtDeviceIndex,
        ByteString
"EnableDns64" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe AttributeBooleanValue
enableDns64,
        ByteString
"EnableLniAtDeviceIndex"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
enableLniAtDeviceIndex,
        ByteString
"EnableResourceNameDnsAAAARecordOnLaunch"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe AttributeBooleanValue
enableResourceNameDnsAAAARecordOnLaunch,
        ByteString
"EnableResourceNameDnsARecordOnLaunch"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe AttributeBooleanValue
enableResourceNameDnsARecordOnLaunch,
        ByteString
"MapCustomerOwnedIpOnLaunch"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe AttributeBooleanValue
mapCustomerOwnedIpOnLaunch,
        ByteString
"MapPublicIpOnLaunch" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe AttributeBooleanValue
mapPublicIpOnLaunch,
        ByteString
"PrivateDnsHostnameTypeOnLaunch"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe HostnameType
privateDnsHostnameTypeOnLaunch,
        ByteString
"SubnetId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
subnetId
      ]

-- | /See:/ 'newModifySubnetAttributeResponse' smart constructor.
data ModifySubnetAttributeResponse = ModifySubnetAttributeResponse'
  {
  }
  deriving (ModifySubnetAttributeResponse
-> ModifySubnetAttributeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModifySubnetAttributeResponse
-> ModifySubnetAttributeResponse -> Bool
$c/= :: ModifySubnetAttributeResponse
-> ModifySubnetAttributeResponse -> Bool
== :: ModifySubnetAttributeResponse
-> ModifySubnetAttributeResponse -> Bool
$c== :: ModifySubnetAttributeResponse
-> ModifySubnetAttributeResponse -> Bool
Prelude.Eq, ReadPrec [ModifySubnetAttributeResponse]
ReadPrec ModifySubnetAttributeResponse
Int -> ReadS ModifySubnetAttributeResponse
ReadS [ModifySubnetAttributeResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModifySubnetAttributeResponse]
$creadListPrec :: ReadPrec [ModifySubnetAttributeResponse]
readPrec :: ReadPrec ModifySubnetAttributeResponse
$creadPrec :: ReadPrec ModifySubnetAttributeResponse
readList :: ReadS [ModifySubnetAttributeResponse]
$creadList :: ReadS [ModifySubnetAttributeResponse]
readsPrec :: Int -> ReadS ModifySubnetAttributeResponse
$creadsPrec :: Int -> ReadS ModifySubnetAttributeResponse
Prelude.Read, Int -> ModifySubnetAttributeResponse -> ShowS
[ModifySubnetAttributeResponse] -> ShowS
ModifySubnetAttributeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModifySubnetAttributeResponse] -> ShowS
$cshowList :: [ModifySubnetAttributeResponse] -> ShowS
show :: ModifySubnetAttributeResponse -> String
$cshow :: ModifySubnetAttributeResponse -> String
showsPrec :: Int -> ModifySubnetAttributeResponse -> ShowS
$cshowsPrec :: Int -> ModifySubnetAttributeResponse -> ShowS
Prelude.Show, forall x.
Rep ModifySubnetAttributeResponse x
-> ModifySubnetAttributeResponse
forall x.
ModifySubnetAttributeResponse
-> Rep ModifySubnetAttributeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ModifySubnetAttributeResponse x
-> ModifySubnetAttributeResponse
$cfrom :: forall x.
ModifySubnetAttributeResponse
-> Rep ModifySubnetAttributeResponse x
Prelude.Generic)

-- |
-- Create a value of 'ModifySubnetAttributeResponse' 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.
newModifySubnetAttributeResponse ::
  ModifySubnetAttributeResponse
newModifySubnetAttributeResponse :: ModifySubnetAttributeResponse
newModifySubnetAttributeResponse =
  ModifySubnetAttributeResponse
ModifySubnetAttributeResponse'

instance Prelude.NFData ModifySubnetAttributeResponse where
  rnf :: ModifySubnetAttributeResponse -> ()
rnf ModifySubnetAttributeResponse
_ = ()