{-# 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.LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-- 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.LaunchTemplateInstanceNetworkInterfaceSpecificationRequest 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.InstanceIpv6AddressRequest
import Amazonka.EC2.Types.Ipv4PrefixSpecificationRequest
import Amazonka.EC2.Types.Ipv6PrefixSpecificationRequest
import Amazonka.EC2.Types.PrivateIpAddressSpecification
import qualified Amazonka.Prelude as Prelude

-- | The parameters for a network interface.
--
-- /See:/ 'newLaunchTemplateInstanceNetworkInterfaceSpecificationRequest' smart constructor.
data LaunchTemplateInstanceNetworkInterfaceSpecificationRequest = LaunchTemplateInstanceNetworkInterfaceSpecificationRequest'
  { -- | Associates a Carrier IP address with eth0 for a new network interface.
    --
    -- Use this option when you launch an instance in a Wavelength Zone and
    -- want to associate a Carrier IP address with the network interface. For
    -- more information about Carrier IP addresses, see
    -- <https://docs.aws.amazon.com/wavelength/latest/developerguide/how-wavelengths-work.html#provider-owned-ip Carrier IP addresses>
    -- in the /Wavelength Developer Guide/.
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Bool
associateCarrierIpAddress :: Prelude.Maybe Prelude.Bool,
    -- | Associates a public IPv4 address with eth0 for a new network interface.
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Bool
associatePublicIpAddress :: Prelude.Maybe Prelude.Bool,
    -- | Indicates whether the network interface is deleted when the instance is
    -- terminated.
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Bool
deleteOnTermination :: Prelude.Maybe Prelude.Bool,
    -- | A description for the network interface.
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The device index for the network interface attachment.
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
deviceIndex :: Prelude.Maybe Prelude.Int,
    -- | The IDs of one or more security groups.
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [Text]
groups :: Prelude.Maybe [Prelude.Text],
    -- | The type of network interface. To create an Elastic Fabric Adapter
    -- (EFA), specify @efa@. For more information, see
    -- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/efa.html Elastic Fabric Adapter>
    -- in the /Amazon Elastic Compute Cloud User Guide/.
    --
    -- If you are not creating an EFA, specify @interface@ or omit this
    -- parameter.
    --
    -- Valid values: @interface@ | @efa@
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Text
interfaceType :: Prelude.Maybe Prelude.Text,
    -- | The number of IPv4 prefixes to be automatically assigned to the network
    -- interface. You cannot use this option if you use the @Ipv4Prefix@
    -- option.
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
ipv4PrefixCount :: Prelude.Maybe Prelude.Int,
    -- | One or more IPv4 prefixes to be assigned to the network interface. You
    -- cannot use this option if you use the @Ipv4PrefixCount@ option.
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [Ipv4PrefixSpecificationRequest]
ipv4Prefixes :: Prelude.Maybe [Ipv4PrefixSpecificationRequest],
    -- | The number of IPv6 addresses to assign to a network interface. Amazon
    -- EC2 automatically selects the IPv6 addresses from the subnet range. You
    -- can\'t use this option if specifying specific IPv6 addresses.
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
ipv6AddressCount :: Prelude.Maybe Prelude.Int,
    -- | One or more specific IPv6 addresses from the IPv6 CIDR block range of
    -- your subnet. You can\'t use this option if you\'re specifying a number
    -- of IPv6 addresses.
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [InstanceIpv6AddressRequest]
ipv6Addresses :: Prelude.Maybe [InstanceIpv6AddressRequest],
    -- | The number of IPv6 prefixes to be automatically assigned to the network
    -- interface. You cannot use this option if you use the @Ipv6Prefix@
    -- option.
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
ipv6PrefixCount :: Prelude.Maybe Prelude.Int,
    -- | One or more IPv6 prefixes to be assigned to the network interface. You
    -- cannot use this option if you use the @Ipv6PrefixCount@ option.
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [Ipv6PrefixSpecificationRequest]
ipv6Prefixes :: Prelude.Maybe [Ipv6PrefixSpecificationRequest],
    -- | The index of the network card. Some instance types support multiple
    -- network cards. The primary network interface must be assigned to network
    -- card index 0. The default is network card index 0.
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
networkCardIndex :: Prelude.Maybe Prelude.Int,
    -- | The ID of the network interface.
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Text
networkInterfaceId :: Prelude.Maybe Prelude.Text,
    -- | The primary private IPv4 address of the network interface.
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Text
privateIpAddress :: Prelude.Maybe Prelude.Text,
    -- | One or more private IPv4 addresses.
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [PrivateIpAddressSpecification]
privateIpAddresses :: Prelude.Maybe [PrivateIpAddressSpecification],
    -- | The number of secondary private IPv4 addresses to assign to a network
    -- interface.
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
secondaryPrivateIpAddressCount :: Prelude.Maybe Prelude.Int,
    -- | The ID of the subnet for the network interface.
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Text
subnetId :: Prelude.Maybe Prelude.Text
  }
  deriving (LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Bool
$c/= :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Bool
== :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Bool
$c== :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Bool
Prelude.Eq, ReadPrec
  [LaunchTemplateInstanceNetworkInterfaceSpecificationRequest]
ReadPrec LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
Int
-> ReadS LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
ReadS [LaunchTemplateInstanceNetworkInterfaceSpecificationRequest]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec
  [LaunchTemplateInstanceNetworkInterfaceSpecificationRequest]
$creadListPrec :: ReadPrec
  [LaunchTemplateInstanceNetworkInterfaceSpecificationRequest]
readPrec :: ReadPrec LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
$creadPrec :: ReadPrec LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
readList :: ReadS [LaunchTemplateInstanceNetworkInterfaceSpecificationRequest]
$creadList :: ReadS [LaunchTemplateInstanceNetworkInterfaceSpecificationRequest]
readsPrec :: Int
-> ReadS LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
$creadsPrec :: Int
-> ReadS LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
Prelude.Read, Int
-> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> ShowS
[LaunchTemplateInstanceNetworkInterfaceSpecificationRequest]
-> ShowS
LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LaunchTemplateInstanceNetworkInterfaceSpecificationRequest]
-> ShowS
$cshowList :: [LaunchTemplateInstanceNetworkInterfaceSpecificationRequest]
-> ShowS
show :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> String
$cshow :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> String
showsPrec :: Int
-> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> ShowS
$cshowsPrec :: Int
-> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> ShowS
Prelude.Show, forall x.
Rep LaunchTemplateInstanceNetworkInterfaceSpecificationRequest x
-> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
forall x.
LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Rep LaunchTemplateInstanceNetworkInterfaceSpecificationRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep LaunchTemplateInstanceNetworkInterfaceSpecificationRequest x
-> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
$cfrom :: forall x.
LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Rep LaunchTemplateInstanceNetworkInterfaceSpecificationRequest x
Prelude.Generic)

-- |
-- Create a value of 'LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' 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:
--
-- 'associateCarrierIpAddress', 'launchTemplateInstanceNetworkInterfaceSpecificationRequest_associateCarrierIpAddress' - Associates a Carrier IP address with eth0 for a new network interface.
--
-- Use this option when you launch an instance in a Wavelength Zone and
-- want to associate a Carrier IP address with the network interface. For
-- more information about Carrier IP addresses, see
-- <https://docs.aws.amazon.com/wavelength/latest/developerguide/how-wavelengths-work.html#provider-owned-ip Carrier IP addresses>
-- in the /Wavelength Developer Guide/.
--
-- 'associatePublicIpAddress', 'launchTemplateInstanceNetworkInterfaceSpecificationRequest_associatePublicIpAddress' - Associates a public IPv4 address with eth0 for a new network interface.
--
-- 'deleteOnTermination', 'launchTemplateInstanceNetworkInterfaceSpecificationRequest_deleteOnTermination' - Indicates whether the network interface is deleted when the instance is
-- terminated.
--
-- 'description', 'launchTemplateInstanceNetworkInterfaceSpecificationRequest_description' - A description for the network interface.
--
-- 'deviceIndex', 'launchTemplateInstanceNetworkInterfaceSpecificationRequest_deviceIndex' - The device index for the network interface attachment.
--
-- 'groups', 'launchTemplateInstanceNetworkInterfaceSpecificationRequest_groups' - The IDs of one or more security groups.
--
-- 'interfaceType', 'launchTemplateInstanceNetworkInterfaceSpecificationRequest_interfaceType' - The type of network interface. To create an Elastic Fabric Adapter
-- (EFA), specify @efa@. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/efa.html Elastic Fabric Adapter>
-- in the /Amazon Elastic Compute Cloud User Guide/.
--
-- If you are not creating an EFA, specify @interface@ or omit this
-- parameter.
--
-- Valid values: @interface@ | @efa@
--
-- 'ipv4PrefixCount', 'launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv4PrefixCount' - The number of IPv4 prefixes to be automatically assigned to the network
-- interface. You cannot use this option if you use the @Ipv4Prefix@
-- option.
--
-- 'ipv4Prefixes', 'launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv4Prefixes' - One or more IPv4 prefixes to be assigned to the network interface. You
-- cannot use this option if you use the @Ipv4PrefixCount@ option.
--
-- 'ipv6AddressCount', 'launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv6AddressCount' - The number of IPv6 addresses to assign to a network interface. Amazon
-- EC2 automatically selects the IPv6 addresses from the subnet range. You
-- can\'t use this option if specifying specific IPv6 addresses.
--
-- 'ipv6Addresses', 'launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv6Addresses' - One or more specific IPv6 addresses from the IPv6 CIDR block range of
-- your subnet. You can\'t use this option if you\'re specifying a number
-- of IPv6 addresses.
--
-- 'ipv6PrefixCount', 'launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv6PrefixCount' - The number of IPv6 prefixes to be automatically assigned to the network
-- interface. You cannot use this option if you use the @Ipv6Prefix@
-- option.
--
-- 'ipv6Prefixes', 'launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv6Prefixes' - One or more IPv6 prefixes to be assigned to the network interface. You
-- cannot use this option if you use the @Ipv6PrefixCount@ option.
--
-- 'networkCardIndex', 'launchTemplateInstanceNetworkInterfaceSpecificationRequest_networkCardIndex' - The index of the network card. Some instance types support multiple
-- network cards. The primary network interface must be assigned to network
-- card index 0. The default is network card index 0.
--
-- 'networkInterfaceId', 'launchTemplateInstanceNetworkInterfaceSpecificationRequest_networkInterfaceId' - The ID of the network interface.
--
-- 'privateIpAddress', 'launchTemplateInstanceNetworkInterfaceSpecificationRequest_privateIpAddress' - The primary private IPv4 address of the network interface.
--
-- 'privateIpAddresses', 'launchTemplateInstanceNetworkInterfaceSpecificationRequest_privateIpAddresses' - One or more private IPv4 addresses.
--
-- 'secondaryPrivateIpAddressCount', 'launchTemplateInstanceNetworkInterfaceSpecificationRequest_secondaryPrivateIpAddressCount' - The number of secondary private IPv4 addresses to assign to a network
-- interface.
--
-- 'subnetId', 'launchTemplateInstanceNetworkInterfaceSpecificationRequest_subnetId' - The ID of the subnet for the network interface.
newLaunchTemplateInstanceNetworkInterfaceSpecificationRequest ::
  LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
newLaunchTemplateInstanceNetworkInterfaceSpecificationRequest :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
newLaunchTemplateInstanceNetworkInterfaceSpecificationRequest =
  LaunchTemplateInstanceNetworkInterfaceSpecificationRequest'
    { $sel:associateCarrierIpAddress:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Bool
associateCarrierIpAddress =
        forall a. Maybe a
Prelude.Nothing,
      $sel:associatePublicIpAddress:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Bool
associatePublicIpAddress =
        forall a. Maybe a
Prelude.Nothing,
      $sel:deleteOnTermination:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Bool
deleteOnTermination =
        forall a. Maybe a
Prelude.Nothing,
      $sel:description:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Text
description =
        forall a. Maybe a
Prelude.Nothing,
      $sel:deviceIndex:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Int
deviceIndex =
        forall a. Maybe a
Prelude.Nothing,
      $sel:groups:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe [Text]
groups =
        forall a. Maybe a
Prelude.Nothing,
      $sel:interfaceType:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Text
interfaceType =
        forall a. Maybe a
Prelude.Nothing,
      $sel:ipv4PrefixCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Int
ipv4PrefixCount =
        forall a. Maybe a
Prelude.Nothing,
      $sel:ipv4Prefixes:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe [Ipv4PrefixSpecificationRequest]
ipv4Prefixes =
        forall a. Maybe a
Prelude.Nothing,
      $sel:ipv6AddressCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Int
ipv6AddressCount =
        forall a. Maybe a
Prelude.Nothing,
      $sel:ipv6Addresses:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe [InstanceIpv6AddressRequest]
ipv6Addresses =
        forall a. Maybe a
Prelude.Nothing,
      $sel:ipv6PrefixCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Int
ipv6PrefixCount =
        forall a. Maybe a
Prelude.Nothing,
      $sel:ipv6Prefixes:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe [Ipv6PrefixSpecificationRequest]
ipv6Prefixes =
        forall a. Maybe a
Prelude.Nothing,
      $sel:networkCardIndex:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Int
networkCardIndex =
        forall a. Maybe a
Prelude.Nothing,
      $sel:networkInterfaceId:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Text
networkInterfaceId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:privateIpAddress:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Text
privateIpAddress =
        forall a. Maybe a
Prelude.Nothing,
      $sel:privateIpAddresses:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe [PrivateIpAddressSpecification]
privateIpAddresses =
        forall a. Maybe a
Prelude.Nothing,
      $sel:secondaryPrivateIpAddressCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Int
secondaryPrivateIpAddressCount =
        forall a. Maybe a
Prelude.Nothing,
      $sel:subnetId:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Text
subnetId =
        forall a. Maybe a
Prelude.Nothing
    }

-- | Associates a Carrier IP address with eth0 for a new network interface.
--
-- Use this option when you launch an instance in a Wavelength Zone and
-- want to associate a Carrier IP address with the network interface. For
-- more information about Carrier IP addresses, see
-- <https://docs.aws.amazon.com/wavelength/latest/developerguide/how-wavelengths-work.html#provider-owned-ip Carrier IP addresses>
-- in the /Wavelength Developer Guide/.
launchTemplateInstanceNetworkInterfaceSpecificationRequest_associateCarrierIpAddress :: Lens.Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Prelude.Maybe Prelude.Bool)
launchTemplateInstanceNetworkInterfaceSpecificationRequest_associateCarrierIpAddress :: Lens'
  LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
  (Maybe Bool)
launchTemplateInstanceNetworkInterfaceSpecificationRequest_associateCarrierIpAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {Maybe Bool
associateCarrierIpAddress :: Maybe Bool
$sel:associateCarrierIpAddress:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Bool
associateCarrierIpAddress} -> Maybe Bool
associateCarrierIpAddress) (\s :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s@LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {} Maybe Bool
a -> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s {$sel:associateCarrierIpAddress:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Bool
associateCarrierIpAddress = Maybe Bool
a} :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest)

-- | Associates a public IPv4 address with eth0 for a new network interface.
launchTemplateInstanceNetworkInterfaceSpecificationRequest_associatePublicIpAddress :: Lens.Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Prelude.Maybe Prelude.Bool)
launchTemplateInstanceNetworkInterfaceSpecificationRequest_associatePublicIpAddress :: Lens'
  LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
  (Maybe Bool)
launchTemplateInstanceNetworkInterfaceSpecificationRequest_associatePublicIpAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {Maybe Bool
associatePublicIpAddress :: Maybe Bool
$sel:associatePublicIpAddress:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Bool
associatePublicIpAddress} -> Maybe Bool
associatePublicIpAddress) (\s :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s@LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {} Maybe Bool
a -> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s {$sel:associatePublicIpAddress:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Bool
associatePublicIpAddress = Maybe Bool
a} :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest)

-- | Indicates whether the network interface is deleted when the instance is
-- terminated.
launchTemplateInstanceNetworkInterfaceSpecificationRequest_deleteOnTermination :: Lens.Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Prelude.Maybe Prelude.Bool)
launchTemplateInstanceNetworkInterfaceSpecificationRequest_deleteOnTermination :: Lens'
  LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
  (Maybe Bool)
launchTemplateInstanceNetworkInterfaceSpecificationRequest_deleteOnTermination = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {Maybe Bool
deleteOnTermination :: Maybe Bool
$sel:deleteOnTermination:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Bool
deleteOnTermination} -> Maybe Bool
deleteOnTermination) (\s :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s@LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {} Maybe Bool
a -> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s {$sel:deleteOnTermination:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Bool
deleteOnTermination = Maybe Bool
a} :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest)

-- | A description for the network interface.
launchTemplateInstanceNetworkInterfaceSpecificationRequest_description :: Lens.Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Prelude.Maybe Prelude.Text)
launchTemplateInstanceNetworkInterfaceSpecificationRequest_description :: Lens'
  LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
  (Maybe Text)
launchTemplateInstanceNetworkInterfaceSpecificationRequest_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {Maybe Text
description :: Maybe Text
$sel:description:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Text
description} -> Maybe Text
description) (\s :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s@LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {} Maybe Text
a -> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s {$sel:description:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Text
description = Maybe Text
a} :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest)

-- | The device index for the network interface attachment.
launchTemplateInstanceNetworkInterfaceSpecificationRequest_deviceIndex :: Lens.Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Prelude.Maybe Prelude.Int)
launchTemplateInstanceNetworkInterfaceSpecificationRequest_deviceIndex :: Lens'
  LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
  (Maybe Int)
launchTemplateInstanceNetworkInterfaceSpecificationRequest_deviceIndex = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {Maybe Int
deviceIndex :: Maybe Int
$sel:deviceIndex:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
deviceIndex} -> Maybe Int
deviceIndex) (\s :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s@LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {} Maybe Int
a -> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s {$sel:deviceIndex:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Int
deviceIndex = Maybe Int
a} :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest)

-- | The IDs of one or more security groups.
launchTemplateInstanceNetworkInterfaceSpecificationRequest_groups :: Lens.Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Prelude.Maybe [Prelude.Text])
launchTemplateInstanceNetworkInterfaceSpecificationRequest_groups :: Lens'
  LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
  (Maybe [Text])
launchTemplateInstanceNetworkInterfaceSpecificationRequest_groups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {Maybe [Text]
groups :: Maybe [Text]
$sel:groups:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [Text]
groups} -> Maybe [Text]
groups) (\s :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s@LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {} Maybe [Text]
a -> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s {$sel:groups:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe [Text]
groups = Maybe [Text]
a} :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest) 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. To create an Elastic Fabric Adapter
-- (EFA), specify @efa@. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/efa.html Elastic Fabric Adapter>
-- in the /Amazon Elastic Compute Cloud User Guide/.
--
-- If you are not creating an EFA, specify @interface@ or omit this
-- parameter.
--
-- Valid values: @interface@ | @efa@
launchTemplateInstanceNetworkInterfaceSpecificationRequest_interfaceType :: Lens.Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Prelude.Maybe Prelude.Text)
launchTemplateInstanceNetworkInterfaceSpecificationRequest_interfaceType :: Lens'
  LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
  (Maybe Text)
launchTemplateInstanceNetworkInterfaceSpecificationRequest_interfaceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {Maybe Text
interfaceType :: Maybe Text
$sel:interfaceType:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Text
interfaceType} -> Maybe Text
interfaceType) (\s :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s@LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {} Maybe Text
a -> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s {$sel:interfaceType:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Text
interfaceType = Maybe Text
a} :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest)

-- | The number of IPv4 prefixes to be automatically assigned to the network
-- interface. You cannot use this option if you use the @Ipv4Prefix@
-- option.
launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv4PrefixCount :: Lens.Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Prelude.Maybe Prelude.Int)
launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv4PrefixCount :: Lens'
  LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
  (Maybe Int)
launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv4PrefixCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {Maybe Int
ipv4PrefixCount :: Maybe Int
$sel:ipv4PrefixCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
ipv4PrefixCount} -> Maybe Int
ipv4PrefixCount) (\s :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s@LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {} Maybe Int
a -> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s {$sel:ipv4PrefixCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Int
ipv4PrefixCount = Maybe Int
a} :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest)

-- | One or more IPv4 prefixes to be assigned to the network interface. You
-- cannot use this option if you use the @Ipv4PrefixCount@ option.
launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv4Prefixes :: Lens.Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Prelude.Maybe [Ipv4PrefixSpecificationRequest])
launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv4Prefixes :: Lens'
  LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
  (Maybe [Ipv4PrefixSpecificationRequest])
launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv4Prefixes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {Maybe [Ipv4PrefixSpecificationRequest]
ipv4Prefixes :: Maybe [Ipv4PrefixSpecificationRequest]
$sel:ipv4Prefixes:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [Ipv4PrefixSpecificationRequest]
ipv4Prefixes} -> Maybe [Ipv4PrefixSpecificationRequest]
ipv4Prefixes) (\s :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s@LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {} Maybe [Ipv4PrefixSpecificationRequest]
a -> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s {$sel:ipv4Prefixes:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe [Ipv4PrefixSpecificationRequest]
ipv4Prefixes = Maybe [Ipv4PrefixSpecificationRequest]
a} :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest) 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 number of IPv6 addresses to assign to a network interface. Amazon
-- EC2 automatically selects the IPv6 addresses from the subnet range. You
-- can\'t use this option if specifying specific IPv6 addresses.
launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv6AddressCount :: Lens.Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Prelude.Maybe Prelude.Int)
launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv6AddressCount :: Lens'
  LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
  (Maybe Int)
launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv6AddressCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {Maybe Int
ipv6AddressCount :: Maybe Int
$sel:ipv6AddressCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
ipv6AddressCount} -> Maybe Int
ipv6AddressCount) (\s :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s@LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {} Maybe Int
a -> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s {$sel:ipv6AddressCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Int
ipv6AddressCount = Maybe Int
a} :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest)

-- | One or more specific IPv6 addresses from the IPv6 CIDR block range of
-- your subnet. You can\'t use this option if you\'re specifying a number
-- of IPv6 addresses.
launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv6Addresses :: Lens.Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Prelude.Maybe [InstanceIpv6AddressRequest])
launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv6Addresses :: Lens'
  LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
  (Maybe [InstanceIpv6AddressRequest])
launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv6Addresses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {Maybe [InstanceIpv6AddressRequest]
ipv6Addresses :: Maybe [InstanceIpv6AddressRequest]
$sel:ipv6Addresses:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [InstanceIpv6AddressRequest]
ipv6Addresses} -> Maybe [InstanceIpv6AddressRequest]
ipv6Addresses) (\s :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s@LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {} Maybe [InstanceIpv6AddressRequest]
a -> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s {$sel:ipv6Addresses:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe [InstanceIpv6AddressRequest]
ipv6Addresses = Maybe [InstanceIpv6AddressRequest]
a} :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest) 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 number of IPv6 prefixes to be automatically assigned to the network
-- interface. You cannot use this option if you use the @Ipv6Prefix@
-- option.
launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv6PrefixCount :: Lens.Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Prelude.Maybe Prelude.Int)
launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv6PrefixCount :: Lens'
  LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
  (Maybe Int)
launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv6PrefixCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {Maybe Int
ipv6PrefixCount :: Maybe Int
$sel:ipv6PrefixCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
ipv6PrefixCount} -> Maybe Int
ipv6PrefixCount) (\s :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s@LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {} Maybe Int
a -> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s {$sel:ipv6PrefixCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Int
ipv6PrefixCount = Maybe Int
a} :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest)

-- | One or more IPv6 prefixes to be assigned to the network interface. You
-- cannot use this option if you use the @Ipv6PrefixCount@ option.
launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv6Prefixes :: Lens.Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Prelude.Maybe [Ipv6PrefixSpecificationRequest])
launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv6Prefixes :: Lens'
  LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
  (Maybe [Ipv6PrefixSpecificationRequest])
launchTemplateInstanceNetworkInterfaceSpecificationRequest_ipv6Prefixes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {Maybe [Ipv6PrefixSpecificationRequest]
ipv6Prefixes :: Maybe [Ipv6PrefixSpecificationRequest]
$sel:ipv6Prefixes:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [Ipv6PrefixSpecificationRequest]
ipv6Prefixes} -> Maybe [Ipv6PrefixSpecificationRequest]
ipv6Prefixes) (\s :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s@LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {} Maybe [Ipv6PrefixSpecificationRequest]
a -> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s {$sel:ipv6Prefixes:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe [Ipv6PrefixSpecificationRequest]
ipv6Prefixes = Maybe [Ipv6PrefixSpecificationRequest]
a} :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest) 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 index of the network card. Some instance types support multiple
-- network cards. The primary network interface must be assigned to network
-- card index 0. The default is network card index 0.
launchTemplateInstanceNetworkInterfaceSpecificationRequest_networkCardIndex :: Lens.Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Prelude.Maybe Prelude.Int)
launchTemplateInstanceNetworkInterfaceSpecificationRequest_networkCardIndex :: Lens'
  LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
  (Maybe Int)
launchTemplateInstanceNetworkInterfaceSpecificationRequest_networkCardIndex = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {Maybe Int
networkCardIndex :: Maybe Int
$sel:networkCardIndex:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
networkCardIndex} -> Maybe Int
networkCardIndex) (\s :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s@LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {} Maybe Int
a -> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s {$sel:networkCardIndex:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Int
networkCardIndex = Maybe Int
a} :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest)

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

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

-- | One or more private IPv4 addresses.
launchTemplateInstanceNetworkInterfaceSpecificationRequest_privateIpAddresses :: Lens.Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Prelude.Maybe [PrivateIpAddressSpecification])
launchTemplateInstanceNetworkInterfaceSpecificationRequest_privateIpAddresses :: Lens'
  LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
  (Maybe [PrivateIpAddressSpecification])
launchTemplateInstanceNetworkInterfaceSpecificationRequest_privateIpAddresses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {Maybe [PrivateIpAddressSpecification]
privateIpAddresses :: Maybe [PrivateIpAddressSpecification]
$sel:privateIpAddresses:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [PrivateIpAddressSpecification]
privateIpAddresses} -> Maybe [PrivateIpAddressSpecification]
privateIpAddresses) (\s :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s@LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {} Maybe [PrivateIpAddressSpecification]
a -> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s {$sel:privateIpAddresses:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe [PrivateIpAddressSpecification]
privateIpAddresses = Maybe [PrivateIpAddressSpecification]
a} :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest) 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 number of secondary private IPv4 addresses to assign to a network
-- interface.
launchTemplateInstanceNetworkInterfaceSpecificationRequest_secondaryPrivateIpAddressCount :: Lens.Lens' LaunchTemplateInstanceNetworkInterfaceSpecificationRequest (Prelude.Maybe Prelude.Int)
launchTemplateInstanceNetworkInterfaceSpecificationRequest_secondaryPrivateIpAddressCount :: Lens'
  LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
  (Maybe Int)
launchTemplateInstanceNetworkInterfaceSpecificationRequest_secondaryPrivateIpAddressCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {Maybe Int
secondaryPrivateIpAddressCount :: Maybe Int
$sel:secondaryPrivateIpAddressCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
secondaryPrivateIpAddressCount} -> Maybe Int
secondaryPrivateIpAddressCount) (\s :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s@LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {} Maybe Int
a -> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
s {$sel:secondaryPrivateIpAddressCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: Maybe Int
secondaryPrivateIpAddressCount = Maybe Int
a} :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest)

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

instance
  Prelude.Hashable
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
  where
  hashWithSalt :: Int
-> LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Int
hashWithSalt
    Int
_salt
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [InstanceIpv6AddressRequest]
Maybe [Ipv4PrefixSpecificationRequest]
Maybe [Ipv6PrefixSpecificationRequest]
Maybe [PrivateIpAddressSpecification]
Maybe Text
subnetId :: Maybe Text
secondaryPrivateIpAddressCount :: Maybe Int
privateIpAddresses :: Maybe [PrivateIpAddressSpecification]
privateIpAddress :: Maybe Text
networkInterfaceId :: Maybe Text
networkCardIndex :: Maybe Int
ipv6Prefixes :: Maybe [Ipv6PrefixSpecificationRequest]
ipv6PrefixCount :: Maybe Int
ipv6Addresses :: Maybe [InstanceIpv6AddressRequest]
ipv6AddressCount :: Maybe Int
ipv4Prefixes :: Maybe [Ipv4PrefixSpecificationRequest]
ipv4PrefixCount :: Maybe Int
interfaceType :: Maybe Text
groups :: Maybe [Text]
deviceIndex :: Maybe Int
description :: Maybe Text
deleteOnTermination :: Maybe Bool
associatePublicIpAddress :: Maybe Bool
associateCarrierIpAddress :: Maybe Bool
$sel:subnetId:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Text
$sel:secondaryPrivateIpAddressCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
$sel:privateIpAddresses:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [PrivateIpAddressSpecification]
$sel:privateIpAddress:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Text
$sel:networkInterfaceId:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Text
$sel:networkCardIndex:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
$sel:ipv6Prefixes:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [Ipv6PrefixSpecificationRequest]
$sel:ipv6PrefixCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
$sel:ipv6Addresses:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [InstanceIpv6AddressRequest]
$sel:ipv6AddressCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
$sel:ipv4Prefixes:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [Ipv4PrefixSpecificationRequest]
$sel:ipv4PrefixCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
$sel:interfaceType:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Text
$sel:groups:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [Text]
$sel:deviceIndex:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
$sel:description:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Text
$sel:deleteOnTermination:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Bool
$sel:associatePublicIpAddress:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Bool
$sel:associateCarrierIpAddress:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Bool
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
associateCarrierIpAddress
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
associatePublicIpAddress
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
deleteOnTermination
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
deviceIndex
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
groups
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
interfaceType
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
ipv4PrefixCount
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Ipv4PrefixSpecificationRequest]
ipv4Prefixes
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
ipv6AddressCount
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [InstanceIpv6AddressRequest]
ipv6Addresses
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
ipv6PrefixCount
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Ipv6PrefixSpecificationRequest]
ipv6Prefixes
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
networkCardIndex
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
networkInterfaceId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
privateIpAddress
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [PrivateIpAddressSpecification]
privateIpAddresses
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
secondaryPrivateIpAddressCount
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
subnetId

instance
  Prelude.NFData
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
  where
  rnf :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest -> ()
rnf
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [InstanceIpv6AddressRequest]
Maybe [Ipv4PrefixSpecificationRequest]
Maybe [Ipv6PrefixSpecificationRequest]
Maybe [PrivateIpAddressSpecification]
Maybe Text
subnetId :: Maybe Text
secondaryPrivateIpAddressCount :: Maybe Int
privateIpAddresses :: Maybe [PrivateIpAddressSpecification]
privateIpAddress :: Maybe Text
networkInterfaceId :: Maybe Text
networkCardIndex :: Maybe Int
ipv6Prefixes :: Maybe [Ipv6PrefixSpecificationRequest]
ipv6PrefixCount :: Maybe Int
ipv6Addresses :: Maybe [InstanceIpv6AddressRequest]
ipv6AddressCount :: Maybe Int
ipv4Prefixes :: Maybe [Ipv4PrefixSpecificationRequest]
ipv4PrefixCount :: Maybe Int
interfaceType :: Maybe Text
groups :: Maybe [Text]
deviceIndex :: Maybe Int
description :: Maybe Text
deleteOnTermination :: Maybe Bool
associatePublicIpAddress :: Maybe Bool
associateCarrierIpAddress :: Maybe Bool
$sel:subnetId:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Text
$sel:secondaryPrivateIpAddressCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
$sel:privateIpAddresses:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [PrivateIpAddressSpecification]
$sel:privateIpAddress:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Text
$sel:networkInterfaceId:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Text
$sel:networkCardIndex:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
$sel:ipv6Prefixes:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [Ipv6PrefixSpecificationRequest]
$sel:ipv6PrefixCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
$sel:ipv6Addresses:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [InstanceIpv6AddressRequest]
$sel:ipv6AddressCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
$sel:ipv4Prefixes:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [Ipv4PrefixSpecificationRequest]
$sel:ipv4PrefixCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
$sel:interfaceType:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Text
$sel:groups:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [Text]
$sel:deviceIndex:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
$sel:description:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Text
$sel:deleteOnTermination:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Bool
$sel:associatePublicIpAddress:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Bool
$sel:associateCarrierIpAddress:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Bool
..} =
      forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
associateCarrierIpAddress
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
associatePublicIpAddress
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
deleteOnTermination
        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 Int
deviceIndex
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
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 Int
ipv4PrefixCount
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Ipv4PrefixSpecificationRequest]
ipv4Prefixes
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
ipv6AddressCount
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [InstanceIpv6AddressRequest]
ipv6Addresses
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
ipv6PrefixCount
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Ipv6PrefixSpecificationRequest]
ipv6Prefixes
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
networkCardIndex
        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
privateIpAddress
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [PrivateIpAddressSpecification]
privateIpAddresses
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
          Maybe Int
secondaryPrivateIpAddressCount
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
subnetId

instance
  Data.ToQuery
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
  where
  toQuery :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> QueryString
toQuery
    LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [InstanceIpv6AddressRequest]
Maybe [Ipv4PrefixSpecificationRequest]
Maybe [Ipv6PrefixSpecificationRequest]
Maybe [PrivateIpAddressSpecification]
Maybe Text
subnetId :: Maybe Text
secondaryPrivateIpAddressCount :: Maybe Int
privateIpAddresses :: Maybe [PrivateIpAddressSpecification]
privateIpAddress :: Maybe Text
networkInterfaceId :: Maybe Text
networkCardIndex :: Maybe Int
ipv6Prefixes :: Maybe [Ipv6PrefixSpecificationRequest]
ipv6PrefixCount :: Maybe Int
ipv6Addresses :: Maybe [InstanceIpv6AddressRequest]
ipv6AddressCount :: Maybe Int
ipv4Prefixes :: Maybe [Ipv4PrefixSpecificationRequest]
ipv4PrefixCount :: Maybe Int
interfaceType :: Maybe Text
groups :: Maybe [Text]
deviceIndex :: Maybe Int
description :: Maybe Text
deleteOnTermination :: Maybe Bool
associatePublicIpAddress :: Maybe Bool
associateCarrierIpAddress :: Maybe Bool
$sel:subnetId:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Text
$sel:secondaryPrivateIpAddressCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
$sel:privateIpAddresses:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [PrivateIpAddressSpecification]
$sel:privateIpAddress:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Text
$sel:networkInterfaceId:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Text
$sel:networkCardIndex:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
$sel:ipv6Prefixes:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [Ipv6PrefixSpecificationRequest]
$sel:ipv6PrefixCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
$sel:ipv6Addresses:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [InstanceIpv6AddressRequest]
$sel:ipv6AddressCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
$sel:ipv4Prefixes:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [Ipv4PrefixSpecificationRequest]
$sel:ipv4PrefixCount:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
$sel:interfaceType:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Text
$sel:groups:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe [Text]
$sel:deviceIndex:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Int
$sel:description:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Text
$sel:deleteOnTermination:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Bool
$sel:associatePublicIpAddress:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Bool
$sel:associateCarrierIpAddress:LaunchTemplateInstanceNetworkInterfaceSpecificationRequest' :: LaunchTemplateInstanceNetworkInterfaceSpecificationRequest
-> Maybe Bool
..} =
      forall a. Monoid a => [a] -> a
Prelude.mconcat
        [ ByteString
"AssociateCarrierIpAddress"
            forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
associateCarrierIpAddress,
          ByteString
"AssociatePublicIpAddress"
            forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
associatePublicIpAddress,
          ByteString
"DeleteOnTermination" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
deleteOnTermination,
          ByteString
"Description" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
description,
          ByteString
"DeviceIndex" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
deviceIndex,
          forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"SecurityGroupId"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
groups
            ),
          ByteString
"InterfaceType" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
interfaceType,
          ByteString
"Ipv4PrefixCount" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
ipv4PrefixCount,
          forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"Ipv4Prefix"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Ipv4PrefixSpecificationRequest]
ipv4Prefixes
            ),
          ByteString
"Ipv6AddressCount" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
ipv6AddressCount,
          forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"Ipv6Addresses"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [InstanceIpv6AddressRequest]
ipv6Addresses
            ),
          ByteString
"Ipv6PrefixCount" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
ipv6PrefixCount,
          forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"Ipv6Prefix"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Ipv6PrefixSpecificationRequest]
ipv6Prefixes
            ),
          ByteString
"NetworkCardIndex" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
networkCardIndex,
          ByteString
"NetworkInterfaceId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
networkInterfaceId,
          ByteString
"PrivateIpAddress" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
privateIpAddress,
          forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"PrivateIpAddresses"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [PrivateIpAddressSpecification]
privateIpAddresses
            ),
          ByteString
"SecondaryPrivateIpAddressCount"
            forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
secondaryPrivateIpAddressCount,
          ByteString
"SubnetId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
subnetId
        ]