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

-- | Describes a network interface.
--
-- /See:/ 'newInstanceNetworkInterfaceSpecification' smart constructor.
data InstanceNetworkInterfaceSpecification = InstanceNetworkInterfaceSpecification'
  { -- | Indicates whether to assign a carrier IP address to the network
    -- interface.
    --
    -- You can only assign a carrier IP address to a network interface that is
    -- in a subnet in a Wavelength Zone. 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 address>
    -- in the /Amazon Web Services Wavelength Developer Guide/.
    InstanceNetworkInterfaceSpecification -> Maybe Bool
associateCarrierIpAddress :: Prelude.Maybe Prelude.Bool,
    -- | Indicates whether to assign a public IPv4 address to an instance you
    -- launch in a VPC. The public IP address can only be assigned to a network
    -- interface for eth0, and can only be assigned to a new network interface,
    -- not an existing one. You cannot specify more than one network interface
    -- in the request. If launching into a default subnet, the default value is
    -- @true@.
    InstanceNetworkInterfaceSpecification -> Maybe Bool
associatePublicIpAddress :: Prelude.Maybe Prelude.Bool,
    -- | If set to @true@, the interface is deleted when the instance is
    -- terminated. You can specify @true@ only if creating a new network
    -- interface when launching an instance.
    InstanceNetworkInterfaceSpecification -> Maybe Bool
deleteOnTermination :: Prelude.Maybe Prelude.Bool,
    -- | The description of the network interface. Applies only if creating a
    -- network interface when launching an instance.
    InstanceNetworkInterfaceSpecification -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The position of the network interface in the attachment order. A primary
    -- network interface has a device index of 0.
    --
    -- If you specify a network interface when launching an instance, you must
    -- specify the device index.
    InstanceNetworkInterfaceSpecification -> Maybe Int
deviceIndex :: Prelude.Maybe Prelude.Int,
    -- | The IDs of the security groups for the network interface. Applies only
    -- if creating a network interface when launching an instance.
    InstanceNetworkInterfaceSpecification -> Maybe [Text]
groups :: Prelude.Maybe [Prelude.Text],
    -- | The type of network interface.
    --
    -- Valid values: @interface@ | @efa@
    InstanceNetworkInterfaceSpecification -> Maybe Text
interfaceType :: Prelude.Maybe Prelude.Text,
    -- | The number of IPv4 delegated prefixes to be automatically assigned to
    -- the network interface. You cannot use this option if you use the
    -- @Ipv4Prefix@ option.
    InstanceNetworkInterfaceSpecification -> Maybe Int
ipv4PrefixCount :: Prelude.Maybe Prelude.Int,
    -- | The IPv4 delegated prefixes to be assigned to the network interface. You
    -- cannot use this option if you use the @Ipv4PrefixCount@ option.
    InstanceNetworkInterfaceSpecification
-> Maybe [Ipv4PrefixSpecificationRequest]
ipv4Prefixes :: Prelude.Maybe [Ipv4PrefixSpecificationRequest],
    -- | A number of IPv6 addresses to assign to the network interface. Amazon
    -- EC2 chooses the IPv6 addresses from the range of the subnet. You cannot
    -- specify this option and the option to assign specific IPv6 addresses in
    -- the same request. You can specify this option if you\'ve specified a
    -- minimum number of instances to launch.
    InstanceNetworkInterfaceSpecification -> Maybe Int
ipv6AddressCount :: Prelude.Maybe Prelude.Int,
    -- | The IPv6 addresses to assign to the network interface. You cannot
    -- specify this option and the option to assign a number of IPv6 addresses
    -- in the same request. You cannot specify this option if you\'ve specified
    -- a minimum number of instances to launch.
    InstanceNetworkInterfaceSpecification
-> Maybe [InstanceIpv6Address]
ipv6Addresses :: Prelude.Maybe [InstanceIpv6Address],
    -- | The number of IPv6 delegated prefixes to be automatically assigned to
    -- the network interface. You cannot use this option if you use the
    -- @Ipv6Prefix@ option.
    InstanceNetworkInterfaceSpecification -> Maybe Int
ipv6PrefixCount :: Prelude.Maybe Prelude.Int,
    -- | The IPv6 delegated prefixes to be assigned to the network interface. You
    -- cannot use this option if you use the @Ipv6PrefixCount@ option.
    InstanceNetworkInterfaceSpecification
-> 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.
    --
    -- If you are using
    -- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_RequestSpotInstances.html RequestSpotInstances>
    -- to create Spot Instances, omit this parameter because you can’t specify
    -- the network card index when using this API. To specify the network card
    -- index, use
    -- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_RunInstances.html RunInstances>.
    InstanceNetworkInterfaceSpecification -> Maybe Int
networkCardIndex :: Prelude.Maybe Prelude.Int,
    -- | The ID of the network interface.
    --
    -- If you are creating a Spot Fleet, omit this parameter because you can’t
    -- specify a network interface ID in a launch specification.
    InstanceNetworkInterfaceSpecification -> Maybe Text
networkInterfaceId :: Prelude.Maybe Prelude.Text,
    -- | The private IPv4 address of the network interface. Applies only if
    -- creating a network interface when launching an instance. You cannot
    -- specify this option if you\'re launching more than one instance in a
    -- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_RunInstances.html RunInstances>
    -- request.
    InstanceNetworkInterfaceSpecification -> Maybe Text
privateIpAddress :: Prelude.Maybe Prelude.Text,
    -- | The private IPv4 addresses to assign to the network interface. Only one
    -- private IPv4 address can be designated as primary. You cannot specify
    -- this option if you\'re launching more than one instance in a
    -- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_RunInstances.html RunInstances>
    -- request.
    InstanceNetworkInterfaceSpecification
-> Maybe [PrivateIpAddressSpecification]
privateIpAddresses :: Prelude.Maybe [PrivateIpAddressSpecification],
    -- | The number of secondary private IPv4 addresses. You can\'t specify this
    -- option and specify more than one private IP address using the private IP
    -- addresses option. You cannot specify this option if you\'re launching
    -- more than one instance in a
    -- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_RunInstances.html RunInstances>
    -- request.
    InstanceNetworkInterfaceSpecification -> Maybe Int
secondaryPrivateIpAddressCount :: Prelude.Maybe Prelude.Int,
    -- | The ID of the subnet associated with the network interface. Applies only
    -- if creating a network interface when launching an instance.
    InstanceNetworkInterfaceSpecification -> Maybe Text
subnetId :: Prelude.Maybe Prelude.Text
  }
  deriving (InstanceNetworkInterfaceSpecification
-> InstanceNetworkInterfaceSpecification -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InstanceNetworkInterfaceSpecification
-> InstanceNetworkInterfaceSpecification -> Bool
$c/= :: InstanceNetworkInterfaceSpecification
-> InstanceNetworkInterfaceSpecification -> Bool
== :: InstanceNetworkInterfaceSpecification
-> InstanceNetworkInterfaceSpecification -> Bool
$c== :: InstanceNetworkInterfaceSpecification
-> InstanceNetworkInterfaceSpecification -> Bool
Prelude.Eq, ReadPrec [InstanceNetworkInterfaceSpecification]
ReadPrec InstanceNetworkInterfaceSpecification
Int -> ReadS InstanceNetworkInterfaceSpecification
ReadS [InstanceNetworkInterfaceSpecification]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InstanceNetworkInterfaceSpecification]
$creadListPrec :: ReadPrec [InstanceNetworkInterfaceSpecification]
readPrec :: ReadPrec InstanceNetworkInterfaceSpecification
$creadPrec :: ReadPrec InstanceNetworkInterfaceSpecification
readList :: ReadS [InstanceNetworkInterfaceSpecification]
$creadList :: ReadS [InstanceNetworkInterfaceSpecification]
readsPrec :: Int -> ReadS InstanceNetworkInterfaceSpecification
$creadsPrec :: Int -> ReadS InstanceNetworkInterfaceSpecification
Prelude.Read, Int -> InstanceNetworkInterfaceSpecification -> ShowS
[InstanceNetworkInterfaceSpecification] -> ShowS
InstanceNetworkInterfaceSpecification -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InstanceNetworkInterfaceSpecification] -> ShowS
$cshowList :: [InstanceNetworkInterfaceSpecification] -> ShowS
show :: InstanceNetworkInterfaceSpecification -> String
$cshow :: InstanceNetworkInterfaceSpecification -> String
showsPrec :: Int -> InstanceNetworkInterfaceSpecification -> ShowS
$cshowsPrec :: Int -> InstanceNetworkInterfaceSpecification -> ShowS
Prelude.Show, forall x.
Rep InstanceNetworkInterfaceSpecification x
-> InstanceNetworkInterfaceSpecification
forall x.
InstanceNetworkInterfaceSpecification
-> Rep InstanceNetworkInterfaceSpecification x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep InstanceNetworkInterfaceSpecification x
-> InstanceNetworkInterfaceSpecification
$cfrom :: forall x.
InstanceNetworkInterfaceSpecification
-> Rep InstanceNetworkInterfaceSpecification x
Prelude.Generic)

-- |
-- Create a value of 'InstanceNetworkInterfaceSpecification' 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', 'instanceNetworkInterfaceSpecification_associateCarrierIpAddress' - Indicates whether to assign a carrier IP address to the network
-- interface.
--
-- You can only assign a carrier IP address to a network interface that is
-- in a subnet in a Wavelength Zone. 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 address>
-- in the /Amazon Web Services Wavelength Developer Guide/.
--
-- 'associatePublicIpAddress', 'instanceNetworkInterfaceSpecification_associatePublicIpAddress' - Indicates whether to assign a public IPv4 address to an instance you
-- launch in a VPC. The public IP address can only be assigned to a network
-- interface for eth0, and can only be assigned to a new network interface,
-- not an existing one. You cannot specify more than one network interface
-- in the request. If launching into a default subnet, the default value is
-- @true@.
--
-- 'deleteOnTermination', 'instanceNetworkInterfaceSpecification_deleteOnTermination' - If set to @true@, the interface is deleted when the instance is
-- terminated. You can specify @true@ only if creating a new network
-- interface when launching an instance.
--
-- 'description', 'instanceNetworkInterfaceSpecification_description' - The description of the network interface. Applies only if creating a
-- network interface when launching an instance.
--
-- 'deviceIndex', 'instanceNetworkInterfaceSpecification_deviceIndex' - The position of the network interface in the attachment order. A primary
-- network interface has a device index of 0.
--
-- If you specify a network interface when launching an instance, you must
-- specify the device index.
--
-- 'groups', 'instanceNetworkInterfaceSpecification_groups' - The IDs of the security groups for the network interface. Applies only
-- if creating a network interface when launching an instance.
--
-- 'interfaceType', 'instanceNetworkInterfaceSpecification_interfaceType' - The type of network interface.
--
-- Valid values: @interface@ | @efa@
--
-- 'ipv4PrefixCount', 'instanceNetworkInterfaceSpecification_ipv4PrefixCount' - The number of IPv4 delegated prefixes to be automatically assigned to
-- the network interface. You cannot use this option if you use the
-- @Ipv4Prefix@ option.
--
-- 'ipv4Prefixes', 'instanceNetworkInterfaceSpecification_ipv4Prefixes' - The IPv4 delegated prefixes to be assigned to the network interface. You
-- cannot use this option if you use the @Ipv4PrefixCount@ option.
--
-- 'ipv6AddressCount', 'instanceNetworkInterfaceSpecification_ipv6AddressCount' - A number of IPv6 addresses to assign to the network interface. Amazon
-- EC2 chooses the IPv6 addresses from the range of the subnet. You cannot
-- specify this option and the option to assign specific IPv6 addresses in
-- the same request. You can specify this option if you\'ve specified a
-- minimum number of instances to launch.
--
-- 'ipv6Addresses', 'instanceNetworkInterfaceSpecification_ipv6Addresses' - The IPv6 addresses to assign to the network interface. You cannot
-- specify this option and the option to assign a number of IPv6 addresses
-- in the same request. You cannot specify this option if you\'ve specified
-- a minimum number of instances to launch.
--
-- 'ipv6PrefixCount', 'instanceNetworkInterfaceSpecification_ipv6PrefixCount' - The number of IPv6 delegated prefixes to be automatically assigned to
-- the network interface. You cannot use this option if you use the
-- @Ipv6Prefix@ option.
--
-- 'ipv6Prefixes', 'instanceNetworkInterfaceSpecification_ipv6Prefixes' - The IPv6 delegated prefixes to be assigned to the network interface. You
-- cannot use this option if you use the @Ipv6PrefixCount@ option.
--
-- 'networkCardIndex', 'instanceNetworkInterfaceSpecification_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.
--
-- If you are using
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_RequestSpotInstances.html RequestSpotInstances>
-- to create Spot Instances, omit this parameter because you can’t specify
-- the network card index when using this API. To specify the network card
-- index, use
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_RunInstances.html RunInstances>.
--
-- 'networkInterfaceId', 'instanceNetworkInterfaceSpecification_networkInterfaceId' - The ID of the network interface.
--
-- If you are creating a Spot Fleet, omit this parameter because you can’t
-- specify a network interface ID in a launch specification.
--
-- 'privateIpAddress', 'instanceNetworkInterfaceSpecification_privateIpAddress' - The private IPv4 address of the network interface. Applies only if
-- creating a network interface when launching an instance. You cannot
-- specify this option if you\'re launching more than one instance in a
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_RunInstances.html RunInstances>
-- request.
--
-- 'privateIpAddresses', 'instanceNetworkInterfaceSpecification_privateIpAddresses' - The private IPv4 addresses to assign to the network interface. Only one
-- private IPv4 address can be designated as primary. You cannot specify
-- this option if you\'re launching more than one instance in a
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_RunInstances.html RunInstances>
-- request.
--
-- 'secondaryPrivateIpAddressCount', 'instanceNetworkInterfaceSpecification_secondaryPrivateIpAddressCount' - The number of secondary private IPv4 addresses. You can\'t specify this
-- option and specify more than one private IP address using the private IP
-- addresses option. You cannot specify this option if you\'re launching
-- more than one instance in a
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_RunInstances.html RunInstances>
-- request.
--
-- 'subnetId', 'instanceNetworkInterfaceSpecification_subnetId' - The ID of the subnet associated with the network interface. Applies only
-- if creating a network interface when launching an instance.
newInstanceNetworkInterfaceSpecification ::
  InstanceNetworkInterfaceSpecification
newInstanceNetworkInterfaceSpecification :: InstanceNetworkInterfaceSpecification
newInstanceNetworkInterfaceSpecification =
  InstanceNetworkInterfaceSpecification'
    { $sel:associateCarrierIpAddress:InstanceNetworkInterfaceSpecification' :: Maybe Bool
associateCarrierIpAddress =
        forall a. Maybe a
Prelude.Nothing,
      $sel:associatePublicIpAddress:InstanceNetworkInterfaceSpecification' :: Maybe Bool
associatePublicIpAddress =
        forall a. Maybe a
Prelude.Nothing,
      $sel:deleteOnTermination:InstanceNetworkInterfaceSpecification' :: Maybe Bool
deleteOnTermination =
        forall a. Maybe a
Prelude.Nothing,
      $sel:description:InstanceNetworkInterfaceSpecification' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:deviceIndex:InstanceNetworkInterfaceSpecification' :: Maybe Int
deviceIndex = forall a. Maybe a
Prelude.Nothing,
      $sel:groups:InstanceNetworkInterfaceSpecification' :: Maybe [Text]
groups = forall a. Maybe a
Prelude.Nothing,
      $sel:interfaceType:InstanceNetworkInterfaceSpecification' :: Maybe Text
interfaceType = forall a. Maybe a
Prelude.Nothing,
      $sel:ipv4PrefixCount:InstanceNetworkInterfaceSpecification' :: Maybe Int
ipv4PrefixCount = forall a. Maybe a
Prelude.Nothing,
      $sel:ipv4Prefixes:InstanceNetworkInterfaceSpecification' :: Maybe [Ipv4PrefixSpecificationRequest]
ipv4Prefixes = forall a. Maybe a
Prelude.Nothing,
      $sel:ipv6AddressCount:InstanceNetworkInterfaceSpecification' :: Maybe Int
ipv6AddressCount = forall a. Maybe a
Prelude.Nothing,
      $sel:ipv6Addresses:InstanceNetworkInterfaceSpecification' :: Maybe [InstanceIpv6Address]
ipv6Addresses = forall a. Maybe a
Prelude.Nothing,
      $sel:ipv6PrefixCount:InstanceNetworkInterfaceSpecification' :: Maybe Int
ipv6PrefixCount = forall a. Maybe a
Prelude.Nothing,
      $sel:ipv6Prefixes:InstanceNetworkInterfaceSpecification' :: Maybe [Ipv6PrefixSpecificationRequest]
ipv6Prefixes = forall a. Maybe a
Prelude.Nothing,
      $sel:networkCardIndex:InstanceNetworkInterfaceSpecification' :: Maybe Int
networkCardIndex = forall a. Maybe a
Prelude.Nothing,
      $sel:networkInterfaceId:InstanceNetworkInterfaceSpecification' :: Maybe Text
networkInterfaceId = forall a. Maybe a
Prelude.Nothing,
      $sel:privateIpAddress:InstanceNetworkInterfaceSpecification' :: Maybe Text
privateIpAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:privateIpAddresses:InstanceNetworkInterfaceSpecification' :: Maybe [PrivateIpAddressSpecification]
privateIpAddresses = forall a. Maybe a
Prelude.Nothing,
      $sel:secondaryPrivateIpAddressCount:InstanceNetworkInterfaceSpecification' :: Maybe Int
secondaryPrivateIpAddressCount =
        forall a. Maybe a
Prelude.Nothing,
      $sel:subnetId:InstanceNetworkInterfaceSpecification' :: Maybe Text
subnetId = forall a. Maybe a
Prelude.Nothing
    }

-- | Indicates whether to assign a carrier IP address to the network
-- interface.
--
-- You can only assign a carrier IP address to a network interface that is
-- in a subnet in a Wavelength Zone. 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 address>
-- in the /Amazon Web Services Wavelength Developer Guide/.
instanceNetworkInterfaceSpecification_associateCarrierIpAddress :: Lens.Lens' InstanceNetworkInterfaceSpecification (Prelude.Maybe Prelude.Bool)
instanceNetworkInterfaceSpecification_associateCarrierIpAddress :: Lens' InstanceNetworkInterfaceSpecification (Maybe Bool)
instanceNetworkInterfaceSpecification_associateCarrierIpAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterfaceSpecification' {Maybe Bool
associateCarrierIpAddress :: Maybe Bool
$sel:associateCarrierIpAddress:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Bool
associateCarrierIpAddress} -> Maybe Bool
associateCarrierIpAddress) (\s :: InstanceNetworkInterfaceSpecification
s@InstanceNetworkInterfaceSpecification' {} Maybe Bool
a -> InstanceNetworkInterfaceSpecification
s {$sel:associateCarrierIpAddress:InstanceNetworkInterfaceSpecification' :: Maybe Bool
associateCarrierIpAddress = Maybe Bool
a} :: InstanceNetworkInterfaceSpecification)

-- | Indicates whether to assign a public IPv4 address to an instance you
-- launch in a VPC. The public IP address can only be assigned to a network
-- interface for eth0, and can only be assigned to a new network interface,
-- not an existing one. You cannot specify more than one network interface
-- in the request. If launching into a default subnet, the default value is
-- @true@.
instanceNetworkInterfaceSpecification_associatePublicIpAddress :: Lens.Lens' InstanceNetworkInterfaceSpecification (Prelude.Maybe Prelude.Bool)
instanceNetworkInterfaceSpecification_associatePublicIpAddress :: Lens' InstanceNetworkInterfaceSpecification (Maybe Bool)
instanceNetworkInterfaceSpecification_associatePublicIpAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterfaceSpecification' {Maybe Bool
associatePublicIpAddress :: Maybe Bool
$sel:associatePublicIpAddress:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Bool
associatePublicIpAddress} -> Maybe Bool
associatePublicIpAddress) (\s :: InstanceNetworkInterfaceSpecification
s@InstanceNetworkInterfaceSpecification' {} Maybe Bool
a -> InstanceNetworkInterfaceSpecification
s {$sel:associatePublicIpAddress:InstanceNetworkInterfaceSpecification' :: Maybe Bool
associatePublicIpAddress = Maybe Bool
a} :: InstanceNetworkInterfaceSpecification)

-- | If set to @true@, the interface is deleted when the instance is
-- terminated. You can specify @true@ only if creating a new network
-- interface when launching an instance.
instanceNetworkInterfaceSpecification_deleteOnTermination :: Lens.Lens' InstanceNetworkInterfaceSpecification (Prelude.Maybe Prelude.Bool)
instanceNetworkInterfaceSpecification_deleteOnTermination :: Lens' InstanceNetworkInterfaceSpecification (Maybe Bool)
instanceNetworkInterfaceSpecification_deleteOnTermination = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterfaceSpecification' {Maybe Bool
deleteOnTermination :: Maybe Bool
$sel:deleteOnTermination:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Bool
deleteOnTermination} -> Maybe Bool
deleteOnTermination) (\s :: InstanceNetworkInterfaceSpecification
s@InstanceNetworkInterfaceSpecification' {} Maybe Bool
a -> InstanceNetworkInterfaceSpecification
s {$sel:deleteOnTermination:InstanceNetworkInterfaceSpecification' :: Maybe Bool
deleteOnTermination = Maybe Bool
a} :: InstanceNetworkInterfaceSpecification)

-- | The description of the network interface. Applies only if creating a
-- network interface when launching an instance.
instanceNetworkInterfaceSpecification_description :: Lens.Lens' InstanceNetworkInterfaceSpecification (Prelude.Maybe Prelude.Text)
instanceNetworkInterfaceSpecification_description :: Lens' InstanceNetworkInterfaceSpecification (Maybe Text)
instanceNetworkInterfaceSpecification_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterfaceSpecification' {Maybe Text
description :: Maybe Text
$sel:description:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Text
description} -> Maybe Text
description) (\s :: InstanceNetworkInterfaceSpecification
s@InstanceNetworkInterfaceSpecification' {} Maybe Text
a -> InstanceNetworkInterfaceSpecification
s {$sel:description:InstanceNetworkInterfaceSpecification' :: Maybe Text
description = Maybe Text
a} :: InstanceNetworkInterfaceSpecification)

-- | The position of the network interface in the attachment order. A primary
-- network interface has a device index of 0.
--
-- If you specify a network interface when launching an instance, you must
-- specify the device index.
instanceNetworkInterfaceSpecification_deviceIndex :: Lens.Lens' InstanceNetworkInterfaceSpecification (Prelude.Maybe Prelude.Int)
instanceNetworkInterfaceSpecification_deviceIndex :: Lens' InstanceNetworkInterfaceSpecification (Maybe Int)
instanceNetworkInterfaceSpecification_deviceIndex = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterfaceSpecification' {Maybe Int
deviceIndex :: Maybe Int
$sel:deviceIndex:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
deviceIndex} -> Maybe Int
deviceIndex) (\s :: InstanceNetworkInterfaceSpecification
s@InstanceNetworkInterfaceSpecification' {} Maybe Int
a -> InstanceNetworkInterfaceSpecification
s {$sel:deviceIndex:InstanceNetworkInterfaceSpecification' :: Maybe Int
deviceIndex = Maybe Int
a} :: InstanceNetworkInterfaceSpecification)

-- | The IDs of the security groups for the network interface. Applies only
-- if creating a network interface when launching an instance.
instanceNetworkInterfaceSpecification_groups :: Lens.Lens' InstanceNetworkInterfaceSpecification (Prelude.Maybe [Prelude.Text])
instanceNetworkInterfaceSpecification_groups :: Lens' InstanceNetworkInterfaceSpecification (Maybe [Text])
instanceNetworkInterfaceSpecification_groups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterfaceSpecification' {Maybe [Text]
groups :: Maybe [Text]
$sel:groups:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe [Text]
groups} -> Maybe [Text]
groups) (\s :: InstanceNetworkInterfaceSpecification
s@InstanceNetworkInterfaceSpecification' {} Maybe [Text]
a -> InstanceNetworkInterfaceSpecification
s {$sel:groups:InstanceNetworkInterfaceSpecification' :: Maybe [Text]
groups = Maybe [Text]
a} :: InstanceNetworkInterfaceSpecification) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The type of network interface.
--
-- Valid values: @interface@ | @efa@
instanceNetworkInterfaceSpecification_interfaceType :: Lens.Lens' InstanceNetworkInterfaceSpecification (Prelude.Maybe Prelude.Text)
instanceNetworkInterfaceSpecification_interfaceType :: Lens' InstanceNetworkInterfaceSpecification (Maybe Text)
instanceNetworkInterfaceSpecification_interfaceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterfaceSpecification' {Maybe Text
interfaceType :: Maybe Text
$sel:interfaceType:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Text
interfaceType} -> Maybe Text
interfaceType) (\s :: InstanceNetworkInterfaceSpecification
s@InstanceNetworkInterfaceSpecification' {} Maybe Text
a -> InstanceNetworkInterfaceSpecification
s {$sel:interfaceType:InstanceNetworkInterfaceSpecification' :: Maybe Text
interfaceType = Maybe Text
a} :: InstanceNetworkInterfaceSpecification)

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

-- | The IPv4 delegated prefixes to be assigned to the network interface. You
-- cannot use this option if you use the @Ipv4PrefixCount@ option.
instanceNetworkInterfaceSpecification_ipv4Prefixes :: Lens.Lens' InstanceNetworkInterfaceSpecification (Prelude.Maybe [Ipv4PrefixSpecificationRequest])
instanceNetworkInterfaceSpecification_ipv4Prefixes :: Lens'
  InstanceNetworkInterfaceSpecification
  (Maybe [Ipv4PrefixSpecificationRequest])
instanceNetworkInterfaceSpecification_ipv4Prefixes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterfaceSpecification' {Maybe [Ipv4PrefixSpecificationRequest]
ipv4Prefixes :: Maybe [Ipv4PrefixSpecificationRequest]
$sel:ipv4Prefixes:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification
-> Maybe [Ipv4PrefixSpecificationRequest]
ipv4Prefixes} -> Maybe [Ipv4PrefixSpecificationRequest]
ipv4Prefixes) (\s :: InstanceNetworkInterfaceSpecification
s@InstanceNetworkInterfaceSpecification' {} Maybe [Ipv4PrefixSpecificationRequest]
a -> InstanceNetworkInterfaceSpecification
s {$sel:ipv4Prefixes:InstanceNetworkInterfaceSpecification' :: Maybe [Ipv4PrefixSpecificationRequest]
ipv4Prefixes = Maybe [Ipv4PrefixSpecificationRequest]
a} :: InstanceNetworkInterfaceSpecification) 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

-- | A number of IPv6 addresses to assign to the network interface. Amazon
-- EC2 chooses the IPv6 addresses from the range of the subnet. You cannot
-- specify this option and the option to assign specific IPv6 addresses in
-- the same request. You can specify this option if you\'ve specified a
-- minimum number of instances to launch.
instanceNetworkInterfaceSpecification_ipv6AddressCount :: Lens.Lens' InstanceNetworkInterfaceSpecification (Prelude.Maybe Prelude.Int)
instanceNetworkInterfaceSpecification_ipv6AddressCount :: Lens' InstanceNetworkInterfaceSpecification (Maybe Int)
instanceNetworkInterfaceSpecification_ipv6AddressCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterfaceSpecification' {Maybe Int
ipv6AddressCount :: Maybe Int
$sel:ipv6AddressCount:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
ipv6AddressCount} -> Maybe Int
ipv6AddressCount) (\s :: InstanceNetworkInterfaceSpecification
s@InstanceNetworkInterfaceSpecification' {} Maybe Int
a -> InstanceNetworkInterfaceSpecification
s {$sel:ipv6AddressCount:InstanceNetworkInterfaceSpecification' :: Maybe Int
ipv6AddressCount = Maybe Int
a} :: InstanceNetworkInterfaceSpecification)

-- | The IPv6 addresses to assign to the network interface. You cannot
-- specify this option and the option to assign a number of IPv6 addresses
-- in the same request. You cannot specify this option if you\'ve specified
-- a minimum number of instances to launch.
instanceNetworkInterfaceSpecification_ipv6Addresses :: Lens.Lens' InstanceNetworkInterfaceSpecification (Prelude.Maybe [InstanceIpv6Address])
instanceNetworkInterfaceSpecification_ipv6Addresses :: Lens'
  InstanceNetworkInterfaceSpecification (Maybe [InstanceIpv6Address])
instanceNetworkInterfaceSpecification_ipv6Addresses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterfaceSpecification' {Maybe [InstanceIpv6Address]
ipv6Addresses :: Maybe [InstanceIpv6Address]
$sel:ipv6Addresses:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification
-> Maybe [InstanceIpv6Address]
ipv6Addresses} -> Maybe [InstanceIpv6Address]
ipv6Addresses) (\s :: InstanceNetworkInterfaceSpecification
s@InstanceNetworkInterfaceSpecification' {} Maybe [InstanceIpv6Address]
a -> InstanceNetworkInterfaceSpecification
s {$sel:ipv6Addresses:InstanceNetworkInterfaceSpecification' :: Maybe [InstanceIpv6Address]
ipv6Addresses = Maybe [InstanceIpv6Address]
a} :: InstanceNetworkInterfaceSpecification) 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 delegated prefixes to be automatically assigned to
-- the network interface. You cannot use this option if you use the
-- @Ipv6Prefix@ option.
instanceNetworkInterfaceSpecification_ipv6PrefixCount :: Lens.Lens' InstanceNetworkInterfaceSpecification (Prelude.Maybe Prelude.Int)
instanceNetworkInterfaceSpecification_ipv6PrefixCount :: Lens' InstanceNetworkInterfaceSpecification (Maybe Int)
instanceNetworkInterfaceSpecification_ipv6PrefixCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterfaceSpecification' {Maybe Int
ipv6PrefixCount :: Maybe Int
$sel:ipv6PrefixCount:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
ipv6PrefixCount} -> Maybe Int
ipv6PrefixCount) (\s :: InstanceNetworkInterfaceSpecification
s@InstanceNetworkInterfaceSpecification' {} Maybe Int
a -> InstanceNetworkInterfaceSpecification
s {$sel:ipv6PrefixCount:InstanceNetworkInterfaceSpecification' :: Maybe Int
ipv6PrefixCount = Maybe Int
a} :: InstanceNetworkInterfaceSpecification)

-- | The IPv6 delegated prefixes to be assigned to the network interface. You
-- cannot use this option if you use the @Ipv6PrefixCount@ option.
instanceNetworkInterfaceSpecification_ipv6Prefixes :: Lens.Lens' InstanceNetworkInterfaceSpecification (Prelude.Maybe [Ipv6PrefixSpecificationRequest])
instanceNetworkInterfaceSpecification_ipv6Prefixes :: Lens'
  InstanceNetworkInterfaceSpecification
  (Maybe [Ipv6PrefixSpecificationRequest])
instanceNetworkInterfaceSpecification_ipv6Prefixes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterfaceSpecification' {Maybe [Ipv6PrefixSpecificationRequest]
ipv6Prefixes :: Maybe [Ipv6PrefixSpecificationRequest]
$sel:ipv6Prefixes:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification
-> Maybe [Ipv6PrefixSpecificationRequest]
ipv6Prefixes} -> Maybe [Ipv6PrefixSpecificationRequest]
ipv6Prefixes) (\s :: InstanceNetworkInterfaceSpecification
s@InstanceNetworkInterfaceSpecification' {} Maybe [Ipv6PrefixSpecificationRequest]
a -> InstanceNetworkInterfaceSpecification
s {$sel:ipv6Prefixes:InstanceNetworkInterfaceSpecification' :: Maybe [Ipv6PrefixSpecificationRequest]
ipv6Prefixes = Maybe [Ipv6PrefixSpecificationRequest]
a} :: InstanceNetworkInterfaceSpecification) 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.
--
-- If you are using
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_RequestSpotInstances.html RequestSpotInstances>
-- to create Spot Instances, omit this parameter because you can’t specify
-- the network card index when using this API. To specify the network card
-- index, use
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_RunInstances.html RunInstances>.
instanceNetworkInterfaceSpecification_networkCardIndex :: Lens.Lens' InstanceNetworkInterfaceSpecification (Prelude.Maybe Prelude.Int)
instanceNetworkInterfaceSpecification_networkCardIndex :: Lens' InstanceNetworkInterfaceSpecification (Maybe Int)
instanceNetworkInterfaceSpecification_networkCardIndex = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterfaceSpecification' {Maybe Int
networkCardIndex :: Maybe Int
$sel:networkCardIndex:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
networkCardIndex} -> Maybe Int
networkCardIndex) (\s :: InstanceNetworkInterfaceSpecification
s@InstanceNetworkInterfaceSpecification' {} Maybe Int
a -> InstanceNetworkInterfaceSpecification
s {$sel:networkCardIndex:InstanceNetworkInterfaceSpecification' :: Maybe Int
networkCardIndex = Maybe Int
a} :: InstanceNetworkInterfaceSpecification)

-- | The ID of the network interface.
--
-- If you are creating a Spot Fleet, omit this parameter because you can’t
-- specify a network interface ID in a launch specification.
instanceNetworkInterfaceSpecification_networkInterfaceId :: Lens.Lens' InstanceNetworkInterfaceSpecification (Prelude.Maybe Prelude.Text)
instanceNetworkInterfaceSpecification_networkInterfaceId :: Lens' InstanceNetworkInterfaceSpecification (Maybe Text)
instanceNetworkInterfaceSpecification_networkInterfaceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterfaceSpecification' {Maybe Text
networkInterfaceId :: Maybe Text
$sel:networkInterfaceId:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Text
networkInterfaceId} -> Maybe Text
networkInterfaceId) (\s :: InstanceNetworkInterfaceSpecification
s@InstanceNetworkInterfaceSpecification' {} Maybe Text
a -> InstanceNetworkInterfaceSpecification
s {$sel:networkInterfaceId:InstanceNetworkInterfaceSpecification' :: Maybe Text
networkInterfaceId = Maybe Text
a} :: InstanceNetworkInterfaceSpecification)

-- | The private IPv4 address of the network interface. Applies only if
-- creating a network interface when launching an instance. You cannot
-- specify this option if you\'re launching more than one instance in a
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_RunInstances.html RunInstances>
-- request.
instanceNetworkInterfaceSpecification_privateIpAddress :: Lens.Lens' InstanceNetworkInterfaceSpecification (Prelude.Maybe Prelude.Text)
instanceNetworkInterfaceSpecification_privateIpAddress :: Lens' InstanceNetworkInterfaceSpecification (Maybe Text)
instanceNetworkInterfaceSpecification_privateIpAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterfaceSpecification' {Maybe Text
privateIpAddress :: Maybe Text
$sel:privateIpAddress:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Text
privateIpAddress} -> Maybe Text
privateIpAddress) (\s :: InstanceNetworkInterfaceSpecification
s@InstanceNetworkInterfaceSpecification' {} Maybe Text
a -> InstanceNetworkInterfaceSpecification
s {$sel:privateIpAddress:InstanceNetworkInterfaceSpecification' :: Maybe Text
privateIpAddress = Maybe Text
a} :: InstanceNetworkInterfaceSpecification)

-- | The private IPv4 addresses to assign to the network interface. Only one
-- private IPv4 address can be designated as primary. You cannot specify
-- this option if you\'re launching more than one instance in a
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_RunInstances.html RunInstances>
-- request.
instanceNetworkInterfaceSpecification_privateIpAddresses :: Lens.Lens' InstanceNetworkInterfaceSpecification (Prelude.Maybe [PrivateIpAddressSpecification])
instanceNetworkInterfaceSpecification_privateIpAddresses :: Lens'
  InstanceNetworkInterfaceSpecification
  (Maybe [PrivateIpAddressSpecification])
instanceNetworkInterfaceSpecification_privateIpAddresses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterfaceSpecification' {Maybe [PrivateIpAddressSpecification]
privateIpAddresses :: Maybe [PrivateIpAddressSpecification]
$sel:privateIpAddresses:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification
-> Maybe [PrivateIpAddressSpecification]
privateIpAddresses} -> Maybe [PrivateIpAddressSpecification]
privateIpAddresses) (\s :: InstanceNetworkInterfaceSpecification
s@InstanceNetworkInterfaceSpecification' {} Maybe [PrivateIpAddressSpecification]
a -> InstanceNetworkInterfaceSpecification
s {$sel:privateIpAddresses:InstanceNetworkInterfaceSpecification' :: Maybe [PrivateIpAddressSpecification]
privateIpAddresses = Maybe [PrivateIpAddressSpecification]
a} :: InstanceNetworkInterfaceSpecification) 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. You can\'t specify this
-- option and specify more than one private IP address using the private IP
-- addresses option. You cannot specify this option if you\'re launching
-- more than one instance in a
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/API_RunInstances.html RunInstances>
-- request.
instanceNetworkInterfaceSpecification_secondaryPrivateIpAddressCount :: Lens.Lens' InstanceNetworkInterfaceSpecification (Prelude.Maybe Prelude.Int)
instanceNetworkInterfaceSpecification_secondaryPrivateIpAddressCount :: Lens' InstanceNetworkInterfaceSpecification (Maybe Int)
instanceNetworkInterfaceSpecification_secondaryPrivateIpAddressCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterfaceSpecification' {Maybe Int
secondaryPrivateIpAddressCount :: Maybe Int
$sel:secondaryPrivateIpAddressCount:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
secondaryPrivateIpAddressCount} -> Maybe Int
secondaryPrivateIpAddressCount) (\s :: InstanceNetworkInterfaceSpecification
s@InstanceNetworkInterfaceSpecification' {} Maybe Int
a -> InstanceNetworkInterfaceSpecification
s {$sel:secondaryPrivateIpAddressCount:InstanceNetworkInterfaceSpecification' :: Maybe Int
secondaryPrivateIpAddressCount = Maybe Int
a} :: InstanceNetworkInterfaceSpecification)

-- | The ID of the subnet associated with the network interface. Applies only
-- if creating a network interface when launching an instance.
instanceNetworkInterfaceSpecification_subnetId :: Lens.Lens' InstanceNetworkInterfaceSpecification (Prelude.Maybe Prelude.Text)
instanceNetworkInterfaceSpecification_subnetId :: Lens' InstanceNetworkInterfaceSpecification (Maybe Text)
instanceNetworkInterfaceSpecification_subnetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InstanceNetworkInterfaceSpecification' {Maybe Text
subnetId :: Maybe Text
$sel:subnetId:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Text
subnetId} -> Maybe Text
subnetId) (\s :: InstanceNetworkInterfaceSpecification
s@InstanceNetworkInterfaceSpecification' {} Maybe Text
a -> InstanceNetworkInterfaceSpecification
s {$sel:subnetId:InstanceNetworkInterfaceSpecification' :: Maybe Text
subnetId = Maybe Text
a} :: InstanceNetworkInterfaceSpecification)

instance
  Data.FromXML
    InstanceNetworkInterfaceSpecification
  where
  parseXML :: [Node] -> Either String InstanceNetworkInterfaceSpecification
parseXML [Node]
x =
    Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe [Text]
-> Maybe Text
-> Maybe Int
-> Maybe [Ipv4PrefixSpecificationRequest]
-> Maybe Int
-> Maybe [InstanceIpv6Address]
-> Maybe Int
-> Maybe [Ipv6PrefixSpecificationRequest]
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe [PrivateIpAddressSpecification]
-> Maybe Int
-> Maybe Text
-> InstanceNetworkInterfaceSpecification
InstanceNetworkInterfaceSpecification'
      forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"AssociateCarrierIpAddress")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"associatePublicIpAddress")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"deleteOnTermination")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"description")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"deviceIndex")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"SecurityGroupId"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"SecurityGroupId")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"InterfaceType")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Ipv4PrefixCount")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Ipv4Prefix"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ipv6AddressCount")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ipv6AddressesSet"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Ipv6PrefixCount")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Ipv6Prefix"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"NetworkCardIndex")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"networkInterfaceId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"privateIpAddress")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"privateIpAddressesSet"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"secondaryPrivateIpAddressCount")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"subnetId")

instance
  Prelude.Hashable
    InstanceNetworkInterfaceSpecification
  where
  hashWithSalt :: Int -> InstanceNetworkInterfaceSpecification -> Int
hashWithSalt
    Int
_salt
    InstanceNetworkInterfaceSpecification' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [InstanceIpv6Address]
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 [InstanceIpv6Address]
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:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Text
$sel:secondaryPrivateIpAddressCount:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
$sel:privateIpAddresses:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification
-> Maybe [PrivateIpAddressSpecification]
$sel:privateIpAddress:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Text
$sel:networkInterfaceId:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Text
$sel:networkCardIndex:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
$sel:ipv6Prefixes:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification
-> Maybe [Ipv6PrefixSpecificationRequest]
$sel:ipv6PrefixCount:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
$sel:ipv6Addresses:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification
-> Maybe [InstanceIpv6Address]
$sel:ipv6AddressCount:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
$sel:ipv4Prefixes:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification
-> Maybe [Ipv4PrefixSpecificationRequest]
$sel:ipv4PrefixCount:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
$sel:interfaceType:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Text
$sel:groups:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe [Text]
$sel:deviceIndex:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
$sel:description:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Text
$sel:deleteOnTermination:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Bool
$sel:associatePublicIpAddress:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Bool
$sel:associateCarrierIpAddress:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> 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 [InstanceIpv6Address]
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
    InstanceNetworkInterfaceSpecification
  where
  rnf :: InstanceNetworkInterfaceSpecification -> ()
rnf InstanceNetworkInterfaceSpecification' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [InstanceIpv6Address]
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 [InstanceIpv6Address]
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:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Text
$sel:secondaryPrivateIpAddressCount:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
$sel:privateIpAddresses:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification
-> Maybe [PrivateIpAddressSpecification]
$sel:privateIpAddress:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Text
$sel:networkInterfaceId:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Text
$sel:networkCardIndex:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
$sel:ipv6Prefixes:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification
-> Maybe [Ipv6PrefixSpecificationRequest]
$sel:ipv6PrefixCount:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
$sel:ipv6Addresses:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification
-> Maybe [InstanceIpv6Address]
$sel:ipv6AddressCount:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
$sel:ipv4Prefixes:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification
-> Maybe [Ipv4PrefixSpecificationRequest]
$sel:ipv4PrefixCount:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
$sel:interfaceType:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Text
$sel:groups:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe [Text]
$sel:deviceIndex:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
$sel:description:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Text
$sel:deleteOnTermination:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Bool
$sel:associatePublicIpAddress:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Bool
$sel:associateCarrierIpAddress:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> 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 [InstanceIpv6Address]
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
    InstanceNetworkInterfaceSpecification
  where
  toQuery :: InstanceNetworkInterfaceSpecification -> QueryString
toQuery InstanceNetworkInterfaceSpecification' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [InstanceIpv6Address]
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 [InstanceIpv6Address]
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:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Text
$sel:secondaryPrivateIpAddressCount:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
$sel:privateIpAddresses:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification
-> Maybe [PrivateIpAddressSpecification]
$sel:privateIpAddress:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Text
$sel:networkInterfaceId:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Text
$sel:networkCardIndex:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
$sel:ipv6Prefixes:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification
-> Maybe [Ipv6PrefixSpecificationRequest]
$sel:ipv6PrefixCount:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
$sel:ipv6Addresses:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification
-> Maybe [InstanceIpv6Address]
$sel:ipv6AddressCount:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
$sel:ipv4Prefixes:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification
-> Maybe [Ipv4PrefixSpecificationRequest]
$sel:ipv4PrefixCount:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
$sel:interfaceType:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Text
$sel:groups:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe [Text]
$sel:deviceIndex:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Int
$sel:description:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Text
$sel:deleteOnTermination:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Bool
$sel:associatePublicIpAddress:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> Maybe Bool
$sel:associateCarrierIpAddress:InstanceNetworkInterfaceSpecification' :: InstanceNetworkInterfaceSpecification -> 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 [InstanceIpv6Address]
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
      ]