{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.EC2.CreateNetworkInterface
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a network interface in the specified subnet.
--
-- The number of IP addresses you can assign to a network interface varies
-- by instance type. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/using-eni.html#AvailableIpPerENI IP Addresses Per ENI Per Instance Type>
-- in the /Amazon Virtual Private Cloud User Guide/.
--
-- For more information about network interfaces, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/using-eni.html Elastic network interfaces>
-- in the /Amazon Elastic Compute Cloud User Guide/.
module Amazonka.EC2.CreateNetworkInterface
  ( -- * Creating a Request
    CreateNetworkInterface (..),
    newCreateNetworkInterface,

    -- * Request Lenses
    createNetworkInterface_clientToken,
    createNetworkInterface_description,
    createNetworkInterface_dryRun,
    createNetworkInterface_groups,
    createNetworkInterface_interfaceType,
    createNetworkInterface_ipv4PrefixCount,
    createNetworkInterface_ipv4Prefixes,
    createNetworkInterface_ipv6AddressCount,
    createNetworkInterface_ipv6Addresses,
    createNetworkInterface_ipv6PrefixCount,
    createNetworkInterface_ipv6Prefixes,
    createNetworkInterface_privateIpAddress,
    createNetworkInterface_privateIpAddresses,
    createNetworkInterface_secondaryPrivateIpAddressCount,
    createNetworkInterface_tagSpecifications,
    createNetworkInterface_subnetId,

    -- * Destructuring the Response
    CreateNetworkInterfaceResponse (..),
    newCreateNetworkInterfaceResponse,

    -- * Response Lenses
    createNetworkInterfaceResponse_clientToken,
    createNetworkInterfaceResponse_networkInterface,
    createNetworkInterfaceResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCreateNetworkInterface' smart constructor.
data CreateNetworkInterface = CreateNetworkInterface'
  { -- | Unique, case-sensitive identifier that you provide to ensure the
    -- idempotency of the request. For more information, see
    -- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/Run_Instance_Idempotency.html Ensuring Idempotency>.
    CreateNetworkInterface -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | A description for the network interface.
    CreateNetworkInterface -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Checks whether you have the required permissions for the action, without
    -- actually making the request, and provides an error response. If you have
    -- the required permissions, the error response is @DryRunOperation@.
    -- Otherwise, it is @UnauthorizedOperation@.
    CreateNetworkInterface -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The IDs of one or more security groups.
    CreateNetworkInterface -> Maybe [Text]
groups :: Prelude.Maybe [Prelude.Text],
    -- | The type of network interface. The default is @interface@.
    --
    -- The only supported values are @efa@ and @trunk@.
    CreateNetworkInterface -> Maybe NetworkInterfaceCreationType
interfaceType :: Prelude.Maybe NetworkInterfaceCreationType,
    -- | The number of IPv4 prefixes that Amazon Web Services automatically
    -- assigns to the network interface.
    --
    -- You can\'t specify a count of IPv4 prefixes if you\'ve specified one of
    -- the following: specific IPv4 prefixes, specific private IPv4 addresses,
    -- or a count of private IPv4 addresses.
    CreateNetworkInterface -> Maybe Int
ipv4PrefixCount :: Prelude.Maybe Prelude.Int,
    -- | The IPv4 prefixes assigned to the network interface.
    --
    -- You can\'t specify IPv4 prefixes if you\'ve specified one of the
    -- following: a count of IPv4 prefixes, specific private IPv4 addresses, or
    -- a count of private IPv4 addresses.
    CreateNetworkInterface -> 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 specify a count of IPv6 addresses using this parameter if
    -- you\'ve specified one of the following: specific IPv6 addresses,
    -- specific IPv6 prefixes, or a count of IPv6 prefixes.
    --
    -- If your subnet has the @AssignIpv6AddressOnCreation@ attribute set, you
    -- can override that setting by specifying 0 as the IPv6 address count.
    CreateNetworkInterface -> Maybe Int
ipv6AddressCount :: Prelude.Maybe Prelude.Int,
    -- | The IPv6 addresses from the IPv6 CIDR block range of your subnet.
    --
    -- You can\'t specify IPv6 addresses using this parameter if you\'ve
    -- specified one of the following: a count of IPv6 addresses, specific IPv6
    -- prefixes, or a count of IPv6 prefixes.
    CreateNetworkInterface -> Maybe [InstanceIpv6Address]
ipv6Addresses :: Prelude.Maybe [InstanceIpv6Address],
    -- | The number of IPv6 prefixes that Amazon Web Services automatically
    -- assigns to the network interface.
    --
    -- You can\'t specify a count of IPv6 prefixes if you\'ve specified one of
    -- the following: specific IPv6 prefixes, specific IPv6 addresses, or a
    -- count of IPv6 addresses.
    CreateNetworkInterface -> Maybe Int
ipv6PrefixCount :: Prelude.Maybe Prelude.Int,
    -- | The IPv6 prefixes assigned to the network interface.
    --
    -- You can\'t specify IPv6 prefixes if you\'ve specified one of the
    -- following: a count of IPv6 prefixes, specific IPv6 addresses, or a count
    -- of IPv6 addresses.
    CreateNetworkInterface -> Maybe [Ipv6PrefixSpecificationRequest]
ipv6Prefixes :: Prelude.Maybe [Ipv6PrefixSpecificationRequest],
    -- | The primary private IPv4 address of the network interface. If you don\'t
    -- specify an IPv4 address, Amazon EC2 selects one for you from the
    -- subnet\'s IPv4 CIDR range. If you specify an IP address, you cannot
    -- indicate any IP addresses specified in @privateIpAddresses@ as primary
    -- (only one IP address can be designated as primary).
    CreateNetworkInterface -> Maybe Text
privateIpAddress :: Prelude.Maybe Prelude.Text,
    -- | The private IPv4 addresses.
    --
    -- You can\'t specify private IPv4 addresses if you\'ve specified one of
    -- the following: a count of private IPv4 addresses, specific IPv4
    -- prefixes, or a count of IPv4 prefixes.
    CreateNetworkInterface -> Maybe [PrivateIpAddressSpecification]
privateIpAddresses :: Prelude.Maybe [PrivateIpAddressSpecification],
    -- | The number of secondary private IPv4 addresses to assign to a network
    -- interface. When you specify a number of secondary IPv4 addresses, Amazon
    -- EC2 selects these IP addresses within the subnet\'s IPv4 CIDR range. You
    -- can\'t specify this option and specify more than one private IP address
    -- using @privateIpAddresses@.
    --
    -- You can\'t specify a count of private IPv4 addresses if you\'ve
    -- specified one of the following: specific private IPv4 addresses,
    -- specific IPv4 prefixes, or a count of IPv4 prefixes.
    CreateNetworkInterface -> Maybe Int
secondaryPrivateIpAddressCount :: Prelude.Maybe Prelude.Int,
    -- | The tags to apply to the new network interface.
    CreateNetworkInterface -> Maybe [TagSpecification]
tagSpecifications :: Prelude.Maybe [TagSpecification],
    -- | The ID of the subnet to associate with the network interface.
    CreateNetworkInterface -> Text
subnetId :: Prelude.Text
  }
  deriving (CreateNetworkInterface -> CreateNetworkInterface -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateNetworkInterface -> CreateNetworkInterface -> Bool
$c/= :: CreateNetworkInterface -> CreateNetworkInterface -> Bool
== :: CreateNetworkInterface -> CreateNetworkInterface -> Bool
$c== :: CreateNetworkInterface -> CreateNetworkInterface -> Bool
Prelude.Eq, ReadPrec [CreateNetworkInterface]
ReadPrec CreateNetworkInterface
Int -> ReadS CreateNetworkInterface
ReadS [CreateNetworkInterface]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateNetworkInterface]
$creadListPrec :: ReadPrec [CreateNetworkInterface]
readPrec :: ReadPrec CreateNetworkInterface
$creadPrec :: ReadPrec CreateNetworkInterface
readList :: ReadS [CreateNetworkInterface]
$creadList :: ReadS [CreateNetworkInterface]
readsPrec :: Int -> ReadS CreateNetworkInterface
$creadsPrec :: Int -> ReadS CreateNetworkInterface
Prelude.Read, Int -> CreateNetworkInterface -> ShowS
[CreateNetworkInterface] -> ShowS
CreateNetworkInterface -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateNetworkInterface] -> ShowS
$cshowList :: [CreateNetworkInterface] -> ShowS
show :: CreateNetworkInterface -> String
$cshow :: CreateNetworkInterface -> String
showsPrec :: Int -> CreateNetworkInterface -> ShowS
$cshowsPrec :: Int -> CreateNetworkInterface -> ShowS
Prelude.Show, forall x. Rep CreateNetworkInterface x -> CreateNetworkInterface
forall x. CreateNetworkInterface -> Rep CreateNetworkInterface x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateNetworkInterface x -> CreateNetworkInterface
$cfrom :: forall x. CreateNetworkInterface -> Rep CreateNetworkInterface x
Prelude.Generic)

-- |
-- Create a value of 'CreateNetworkInterface' 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:
--
-- 'clientToken', 'createNetworkInterface_clientToken' - Unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/Run_Instance_Idempotency.html Ensuring Idempotency>.
--
-- 'description', 'createNetworkInterface_description' - A description for the network interface.
--
-- 'dryRun', 'createNetworkInterface_dryRun' - Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
--
-- 'groups', 'createNetworkInterface_groups' - The IDs of one or more security groups.
--
-- 'interfaceType', 'createNetworkInterface_interfaceType' - The type of network interface. The default is @interface@.
--
-- The only supported values are @efa@ and @trunk@.
--
-- 'ipv4PrefixCount', 'createNetworkInterface_ipv4PrefixCount' - The number of IPv4 prefixes that Amazon Web Services automatically
-- assigns to the network interface.
--
-- You can\'t specify a count of IPv4 prefixes if you\'ve specified one of
-- the following: specific IPv4 prefixes, specific private IPv4 addresses,
-- or a count of private IPv4 addresses.
--
-- 'ipv4Prefixes', 'createNetworkInterface_ipv4Prefixes' - The IPv4 prefixes assigned to the network interface.
--
-- You can\'t specify IPv4 prefixes if you\'ve specified one of the
-- following: a count of IPv4 prefixes, specific private IPv4 addresses, or
-- a count of private IPv4 addresses.
--
-- 'ipv6AddressCount', 'createNetworkInterface_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 specify a count of IPv6 addresses using this parameter if
-- you\'ve specified one of the following: specific IPv6 addresses,
-- specific IPv6 prefixes, or a count of IPv6 prefixes.
--
-- If your subnet has the @AssignIpv6AddressOnCreation@ attribute set, you
-- can override that setting by specifying 0 as the IPv6 address count.
--
-- 'ipv6Addresses', 'createNetworkInterface_ipv6Addresses' - The IPv6 addresses from the IPv6 CIDR block range of your subnet.
--
-- You can\'t specify IPv6 addresses using this parameter if you\'ve
-- specified one of the following: a count of IPv6 addresses, specific IPv6
-- prefixes, or a count of IPv6 prefixes.
--
-- 'ipv6PrefixCount', 'createNetworkInterface_ipv6PrefixCount' - The number of IPv6 prefixes that Amazon Web Services automatically
-- assigns to the network interface.
--
-- You can\'t specify a count of IPv6 prefixes if you\'ve specified one of
-- the following: specific IPv6 prefixes, specific IPv6 addresses, or a
-- count of IPv6 addresses.
--
-- 'ipv6Prefixes', 'createNetworkInterface_ipv6Prefixes' - The IPv6 prefixes assigned to the network interface.
--
-- You can\'t specify IPv6 prefixes if you\'ve specified one of the
-- following: a count of IPv6 prefixes, specific IPv6 addresses, or a count
-- of IPv6 addresses.
--
-- 'privateIpAddress', 'createNetworkInterface_privateIpAddress' - The primary private IPv4 address of the network interface. If you don\'t
-- specify an IPv4 address, Amazon EC2 selects one for you from the
-- subnet\'s IPv4 CIDR range. If you specify an IP address, you cannot
-- indicate any IP addresses specified in @privateIpAddresses@ as primary
-- (only one IP address can be designated as primary).
--
-- 'privateIpAddresses', 'createNetworkInterface_privateIpAddresses' - The private IPv4 addresses.
--
-- You can\'t specify private IPv4 addresses if you\'ve specified one of
-- the following: a count of private IPv4 addresses, specific IPv4
-- prefixes, or a count of IPv4 prefixes.
--
-- 'secondaryPrivateIpAddressCount', 'createNetworkInterface_secondaryPrivateIpAddressCount' - The number of secondary private IPv4 addresses to assign to a network
-- interface. When you specify a number of secondary IPv4 addresses, Amazon
-- EC2 selects these IP addresses within the subnet\'s IPv4 CIDR range. You
-- can\'t specify this option and specify more than one private IP address
-- using @privateIpAddresses@.
--
-- You can\'t specify a count of private IPv4 addresses if you\'ve
-- specified one of the following: specific private IPv4 addresses,
-- specific IPv4 prefixes, or a count of IPv4 prefixes.
--
-- 'tagSpecifications', 'createNetworkInterface_tagSpecifications' - The tags to apply to the new network interface.
--
-- 'subnetId', 'createNetworkInterface_subnetId' - The ID of the subnet to associate with the network interface.
newCreateNetworkInterface ::
  -- | 'subnetId'
  Prelude.Text ->
  CreateNetworkInterface
newCreateNetworkInterface :: Text -> CreateNetworkInterface
newCreateNetworkInterface Text
pSubnetId_ =
  CreateNetworkInterface'
    { $sel:clientToken:CreateNetworkInterface' :: Maybe Text
clientToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:description:CreateNetworkInterface' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:dryRun:CreateNetworkInterface' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:groups:CreateNetworkInterface' :: Maybe [Text]
groups = forall a. Maybe a
Prelude.Nothing,
      $sel:interfaceType:CreateNetworkInterface' :: Maybe NetworkInterfaceCreationType
interfaceType = forall a. Maybe a
Prelude.Nothing,
      $sel:ipv4PrefixCount:CreateNetworkInterface' :: Maybe Int
ipv4PrefixCount = forall a. Maybe a
Prelude.Nothing,
      $sel:ipv4Prefixes:CreateNetworkInterface' :: Maybe [Ipv4PrefixSpecificationRequest]
ipv4Prefixes = forall a. Maybe a
Prelude.Nothing,
      $sel:ipv6AddressCount:CreateNetworkInterface' :: Maybe Int
ipv6AddressCount = forall a. Maybe a
Prelude.Nothing,
      $sel:ipv6Addresses:CreateNetworkInterface' :: Maybe [InstanceIpv6Address]
ipv6Addresses = forall a. Maybe a
Prelude.Nothing,
      $sel:ipv6PrefixCount:CreateNetworkInterface' :: Maybe Int
ipv6PrefixCount = forall a. Maybe a
Prelude.Nothing,
      $sel:ipv6Prefixes:CreateNetworkInterface' :: Maybe [Ipv6PrefixSpecificationRequest]
ipv6Prefixes = forall a. Maybe a
Prelude.Nothing,
      $sel:privateIpAddress:CreateNetworkInterface' :: Maybe Text
privateIpAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:privateIpAddresses:CreateNetworkInterface' :: Maybe [PrivateIpAddressSpecification]
privateIpAddresses = forall a. Maybe a
Prelude.Nothing,
      $sel:secondaryPrivateIpAddressCount:CreateNetworkInterface' :: Maybe Int
secondaryPrivateIpAddressCount = forall a. Maybe a
Prelude.Nothing,
      $sel:tagSpecifications:CreateNetworkInterface' :: Maybe [TagSpecification]
tagSpecifications = forall a. Maybe a
Prelude.Nothing,
      $sel:subnetId:CreateNetworkInterface' :: Text
subnetId = Text
pSubnetId_
    }

-- | Unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/Run_Instance_Idempotency.html Ensuring Idempotency>.
createNetworkInterface_clientToken :: Lens.Lens' CreateNetworkInterface (Prelude.Maybe Prelude.Text)
createNetworkInterface_clientToken :: Lens' CreateNetworkInterface (Maybe Text)
createNetworkInterface_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNetworkInterface' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: CreateNetworkInterface
s@CreateNetworkInterface' {} Maybe Text
a -> CreateNetworkInterface
s {$sel:clientToken:CreateNetworkInterface' :: Maybe Text
clientToken = Maybe Text
a} :: CreateNetworkInterface)

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

-- | Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
createNetworkInterface_dryRun :: Lens.Lens' CreateNetworkInterface (Prelude.Maybe Prelude.Bool)
createNetworkInterface_dryRun :: Lens' CreateNetworkInterface (Maybe Bool)
createNetworkInterface_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNetworkInterface' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: CreateNetworkInterface
s@CreateNetworkInterface' {} Maybe Bool
a -> CreateNetworkInterface
s {$sel:dryRun:CreateNetworkInterface' :: Maybe Bool
dryRun = Maybe Bool
a} :: CreateNetworkInterface)

-- | The IDs of one or more security groups.
createNetworkInterface_groups :: Lens.Lens' CreateNetworkInterface (Prelude.Maybe [Prelude.Text])
createNetworkInterface_groups :: Lens' CreateNetworkInterface (Maybe [Text])
createNetworkInterface_groups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNetworkInterface' {Maybe [Text]
groups :: Maybe [Text]
$sel:groups:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [Text]
groups} -> Maybe [Text]
groups) (\s :: CreateNetworkInterface
s@CreateNetworkInterface' {} Maybe [Text]
a -> CreateNetworkInterface
s {$sel:groups:CreateNetworkInterface' :: Maybe [Text]
groups = Maybe [Text]
a} :: CreateNetworkInterface) 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. The default is @interface@.
--
-- The only supported values are @efa@ and @trunk@.
createNetworkInterface_interfaceType :: Lens.Lens' CreateNetworkInterface (Prelude.Maybe NetworkInterfaceCreationType)
createNetworkInterface_interfaceType :: Lens' CreateNetworkInterface (Maybe NetworkInterfaceCreationType)
createNetworkInterface_interfaceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNetworkInterface' {Maybe NetworkInterfaceCreationType
interfaceType :: Maybe NetworkInterfaceCreationType
$sel:interfaceType:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe NetworkInterfaceCreationType
interfaceType} -> Maybe NetworkInterfaceCreationType
interfaceType) (\s :: CreateNetworkInterface
s@CreateNetworkInterface' {} Maybe NetworkInterfaceCreationType
a -> CreateNetworkInterface
s {$sel:interfaceType:CreateNetworkInterface' :: Maybe NetworkInterfaceCreationType
interfaceType = Maybe NetworkInterfaceCreationType
a} :: CreateNetworkInterface)

-- | The number of IPv4 prefixes that Amazon Web Services automatically
-- assigns to the network interface.
--
-- You can\'t specify a count of IPv4 prefixes if you\'ve specified one of
-- the following: specific IPv4 prefixes, specific private IPv4 addresses,
-- or a count of private IPv4 addresses.
createNetworkInterface_ipv4PrefixCount :: Lens.Lens' CreateNetworkInterface (Prelude.Maybe Prelude.Int)
createNetworkInterface_ipv4PrefixCount :: Lens' CreateNetworkInterface (Maybe Int)
createNetworkInterface_ipv4PrefixCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNetworkInterface' {Maybe Int
ipv4PrefixCount :: Maybe Int
$sel:ipv4PrefixCount:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Int
ipv4PrefixCount} -> Maybe Int
ipv4PrefixCount) (\s :: CreateNetworkInterface
s@CreateNetworkInterface' {} Maybe Int
a -> CreateNetworkInterface
s {$sel:ipv4PrefixCount:CreateNetworkInterface' :: Maybe Int
ipv4PrefixCount = Maybe Int
a} :: CreateNetworkInterface)

-- | The IPv4 prefixes assigned to the network interface.
--
-- You can\'t specify IPv4 prefixes if you\'ve specified one of the
-- following: a count of IPv4 prefixes, specific private IPv4 addresses, or
-- a count of private IPv4 addresses.
createNetworkInterface_ipv4Prefixes :: Lens.Lens' CreateNetworkInterface (Prelude.Maybe [Ipv4PrefixSpecificationRequest])
createNetworkInterface_ipv4Prefixes :: Lens'
  CreateNetworkInterface (Maybe [Ipv4PrefixSpecificationRequest])
createNetworkInterface_ipv4Prefixes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNetworkInterface' {Maybe [Ipv4PrefixSpecificationRequest]
ipv4Prefixes :: Maybe [Ipv4PrefixSpecificationRequest]
$sel:ipv4Prefixes:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [Ipv4PrefixSpecificationRequest]
ipv4Prefixes} -> Maybe [Ipv4PrefixSpecificationRequest]
ipv4Prefixes) (\s :: CreateNetworkInterface
s@CreateNetworkInterface' {} Maybe [Ipv4PrefixSpecificationRequest]
a -> CreateNetworkInterface
s {$sel:ipv4Prefixes:CreateNetworkInterface' :: Maybe [Ipv4PrefixSpecificationRequest]
ipv4Prefixes = Maybe [Ipv4PrefixSpecificationRequest]
a} :: CreateNetworkInterface) 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 specify a count of IPv6 addresses using this parameter if
-- you\'ve specified one of the following: specific IPv6 addresses,
-- specific IPv6 prefixes, or a count of IPv6 prefixes.
--
-- If your subnet has the @AssignIpv6AddressOnCreation@ attribute set, you
-- can override that setting by specifying 0 as the IPv6 address count.
createNetworkInterface_ipv6AddressCount :: Lens.Lens' CreateNetworkInterface (Prelude.Maybe Prelude.Int)
createNetworkInterface_ipv6AddressCount :: Lens' CreateNetworkInterface (Maybe Int)
createNetworkInterface_ipv6AddressCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNetworkInterface' {Maybe Int
ipv6AddressCount :: Maybe Int
$sel:ipv6AddressCount:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Int
ipv6AddressCount} -> Maybe Int
ipv6AddressCount) (\s :: CreateNetworkInterface
s@CreateNetworkInterface' {} Maybe Int
a -> CreateNetworkInterface
s {$sel:ipv6AddressCount:CreateNetworkInterface' :: Maybe Int
ipv6AddressCount = Maybe Int
a} :: CreateNetworkInterface)

-- | The IPv6 addresses from the IPv6 CIDR block range of your subnet.
--
-- You can\'t specify IPv6 addresses using this parameter if you\'ve
-- specified one of the following: a count of IPv6 addresses, specific IPv6
-- prefixes, or a count of IPv6 prefixes.
createNetworkInterface_ipv6Addresses :: Lens.Lens' CreateNetworkInterface (Prelude.Maybe [InstanceIpv6Address])
createNetworkInterface_ipv6Addresses :: Lens' CreateNetworkInterface (Maybe [InstanceIpv6Address])
createNetworkInterface_ipv6Addresses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNetworkInterface' {Maybe [InstanceIpv6Address]
ipv6Addresses :: Maybe [InstanceIpv6Address]
$sel:ipv6Addresses:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [InstanceIpv6Address]
ipv6Addresses} -> Maybe [InstanceIpv6Address]
ipv6Addresses) (\s :: CreateNetworkInterface
s@CreateNetworkInterface' {} Maybe [InstanceIpv6Address]
a -> CreateNetworkInterface
s {$sel:ipv6Addresses:CreateNetworkInterface' :: Maybe [InstanceIpv6Address]
ipv6Addresses = Maybe [InstanceIpv6Address]
a} :: CreateNetworkInterface) 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 that Amazon Web Services automatically
-- assigns to the network interface.
--
-- You can\'t specify a count of IPv6 prefixes if you\'ve specified one of
-- the following: specific IPv6 prefixes, specific IPv6 addresses, or a
-- count of IPv6 addresses.
createNetworkInterface_ipv6PrefixCount :: Lens.Lens' CreateNetworkInterface (Prelude.Maybe Prelude.Int)
createNetworkInterface_ipv6PrefixCount :: Lens' CreateNetworkInterface (Maybe Int)
createNetworkInterface_ipv6PrefixCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNetworkInterface' {Maybe Int
ipv6PrefixCount :: Maybe Int
$sel:ipv6PrefixCount:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Int
ipv6PrefixCount} -> Maybe Int
ipv6PrefixCount) (\s :: CreateNetworkInterface
s@CreateNetworkInterface' {} Maybe Int
a -> CreateNetworkInterface
s {$sel:ipv6PrefixCount:CreateNetworkInterface' :: Maybe Int
ipv6PrefixCount = Maybe Int
a} :: CreateNetworkInterface)

-- | The IPv6 prefixes assigned to the network interface.
--
-- You can\'t specify IPv6 prefixes if you\'ve specified one of the
-- following: a count of IPv6 prefixes, specific IPv6 addresses, or a count
-- of IPv6 addresses.
createNetworkInterface_ipv6Prefixes :: Lens.Lens' CreateNetworkInterface (Prelude.Maybe [Ipv6PrefixSpecificationRequest])
createNetworkInterface_ipv6Prefixes :: Lens'
  CreateNetworkInterface (Maybe [Ipv6PrefixSpecificationRequest])
createNetworkInterface_ipv6Prefixes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNetworkInterface' {Maybe [Ipv6PrefixSpecificationRequest]
ipv6Prefixes :: Maybe [Ipv6PrefixSpecificationRequest]
$sel:ipv6Prefixes:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [Ipv6PrefixSpecificationRequest]
ipv6Prefixes} -> Maybe [Ipv6PrefixSpecificationRequest]
ipv6Prefixes) (\s :: CreateNetworkInterface
s@CreateNetworkInterface' {} Maybe [Ipv6PrefixSpecificationRequest]
a -> CreateNetworkInterface
s {$sel:ipv6Prefixes:CreateNetworkInterface' :: Maybe [Ipv6PrefixSpecificationRequest]
ipv6Prefixes = Maybe [Ipv6PrefixSpecificationRequest]
a} :: CreateNetworkInterface) 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 primary private IPv4 address of the network interface. If you don\'t
-- specify an IPv4 address, Amazon EC2 selects one for you from the
-- subnet\'s IPv4 CIDR range. If you specify an IP address, you cannot
-- indicate any IP addresses specified in @privateIpAddresses@ as primary
-- (only one IP address can be designated as primary).
createNetworkInterface_privateIpAddress :: Lens.Lens' CreateNetworkInterface (Prelude.Maybe Prelude.Text)
createNetworkInterface_privateIpAddress :: Lens' CreateNetworkInterface (Maybe Text)
createNetworkInterface_privateIpAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNetworkInterface' {Maybe Text
privateIpAddress :: Maybe Text
$sel:privateIpAddress:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Text
privateIpAddress} -> Maybe Text
privateIpAddress) (\s :: CreateNetworkInterface
s@CreateNetworkInterface' {} Maybe Text
a -> CreateNetworkInterface
s {$sel:privateIpAddress:CreateNetworkInterface' :: Maybe Text
privateIpAddress = Maybe Text
a} :: CreateNetworkInterface)

-- | The private IPv4 addresses.
--
-- You can\'t specify private IPv4 addresses if you\'ve specified one of
-- the following: a count of private IPv4 addresses, specific IPv4
-- prefixes, or a count of IPv4 prefixes.
createNetworkInterface_privateIpAddresses :: Lens.Lens' CreateNetworkInterface (Prelude.Maybe [PrivateIpAddressSpecification])
createNetworkInterface_privateIpAddresses :: Lens'
  CreateNetworkInterface (Maybe [PrivateIpAddressSpecification])
createNetworkInterface_privateIpAddresses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNetworkInterface' {Maybe [PrivateIpAddressSpecification]
privateIpAddresses :: Maybe [PrivateIpAddressSpecification]
$sel:privateIpAddresses:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [PrivateIpAddressSpecification]
privateIpAddresses} -> Maybe [PrivateIpAddressSpecification]
privateIpAddresses) (\s :: CreateNetworkInterface
s@CreateNetworkInterface' {} Maybe [PrivateIpAddressSpecification]
a -> CreateNetworkInterface
s {$sel:privateIpAddresses:CreateNetworkInterface' :: Maybe [PrivateIpAddressSpecification]
privateIpAddresses = Maybe [PrivateIpAddressSpecification]
a} :: CreateNetworkInterface) 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. When you specify a number of secondary IPv4 addresses, Amazon
-- EC2 selects these IP addresses within the subnet\'s IPv4 CIDR range. You
-- can\'t specify this option and specify more than one private IP address
-- using @privateIpAddresses@.
--
-- You can\'t specify a count of private IPv4 addresses if you\'ve
-- specified one of the following: specific private IPv4 addresses,
-- specific IPv4 prefixes, or a count of IPv4 prefixes.
createNetworkInterface_secondaryPrivateIpAddressCount :: Lens.Lens' CreateNetworkInterface (Prelude.Maybe Prelude.Int)
createNetworkInterface_secondaryPrivateIpAddressCount :: Lens' CreateNetworkInterface (Maybe Int)
createNetworkInterface_secondaryPrivateIpAddressCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNetworkInterface' {Maybe Int
secondaryPrivateIpAddressCount :: Maybe Int
$sel:secondaryPrivateIpAddressCount:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Int
secondaryPrivateIpAddressCount} -> Maybe Int
secondaryPrivateIpAddressCount) (\s :: CreateNetworkInterface
s@CreateNetworkInterface' {} Maybe Int
a -> CreateNetworkInterface
s {$sel:secondaryPrivateIpAddressCount:CreateNetworkInterface' :: Maybe Int
secondaryPrivateIpAddressCount = Maybe Int
a} :: CreateNetworkInterface)

-- | The tags to apply to the new network interface.
createNetworkInterface_tagSpecifications :: Lens.Lens' CreateNetworkInterface (Prelude.Maybe [TagSpecification])
createNetworkInterface_tagSpecifications :: Lens' CreateNetworkInterface (Maybe [TagSpecification])
createNetworkInterface_tagSpecifications = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNetworkInterface' {Maybe [TagSpecification]
tagSpecifications :: Maybe [TagSpecification]
$sel:tagSpecifications:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [TagSpecification]
tagSpecifications} -> Maybe [TagSpecification]
tagSpecifications) (\s :: CreateNetworkInterface
s@CreateNetworkInterface' {} Maybe [TagSpecification]
a -> CreateNetworkInterface
s {$sel:tagSpecifications:CreateNetworkInterface' :: Maybe [TagSpecification]
tagSpecifications = Maybe [TagSpecification]
a} :: CreateNetworkInterface) 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 ID of the subnet to associate with the network interface.
createNetworkInterface_subnetId :: Lens.Lens' CreateNetworkInterface Prelude.Text
createNetworkInterface_subnetId :: Lens' CreateNetworkInterface Text
createNetworkInterface_subnetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNetworkInterface' {Text
subnetId :: Text
$sel:subnetId:CreateNetworkInterface' :: CreateNetworkInterface -> Text
subnetId} -> Text
subnetId) (\s :: CreateNetworkInterface
s@CreateNetworkInterface' {} Text
a -> CreateNetworkInterface
s {$sel:subnetId:CreateNetworkInterface' :: Text
subnetId = Text
a} :: CreateNetworkInterface)

instance Core.AWSRequest CreateNetworkInterface where
  type
    AWSResponse CreateNetworkInterface =
      CreateNetworkInterfaceResponse
  request :: (Service -> Service)
-> CreateNetworkInterface -> Request CreateNetworkInterface
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateNetworkInterface
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateNetworkInterface)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text
-> Maybe NetworkInterface -> Int -> CreateNetworkInterfaceResponse
CreateNetworkInterfaceResponse'
            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
"clientToken")
            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
"networkInterface")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable CreateNetworkInterface where
  hashWithSalt :: Int -> CreateNetworkInterface -> Int
hashWithSalt Int
_salt CreateNetworkInterface' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [InstanceIpv6Address]
Maybe [Ipv4PrefixSpecificationRequest]
Maybe [Ipv6PrefixSpecificationRequest]
Maybe [PrivateIpAddressSpecification]
Maybe [TagSpecification]
Maybe Text
Maybe NetworkInterfaceCreationType
Text
subnetId :: Text
tagSpecifications :: Maybe [TagSpecification]
secondaryPrivateIpAddressCount :: Maybe Int
privateIpAddresses :: Maybe [PrivateIpAddressSpecification]
privateIpAddress :: Maybe Text
ipv6Prefixes :: Maybe [Ipv6PrefixSpecificationRequest]
ipv6PrefixCount :: Maybe Int
ipv6Addresses :: Maybe [InstanceIpv6Address]
ipv6AddressCount :: Maybe Int
ipv4Prefixes :: Maybe [Ipv4PrefixSpecificationRequest]
ipv4PrefixCount :: Maybe Int
interfaceType :: Maybe NetworkInterfaceCreationType
groups :: Maybe [Text]
dryRun :: Maybe Bool
description :: Maybe Text
clientToken :: Maybe Text
$sel:subnetId:CreateNetworkInterface' :: CreateNetworkInterface -> Text
$sel:tagSpecifications:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [TagSpecification]
$sel:secondaryPrivateIpAddressCount:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Int
$sel:privateIpAddresses:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [PrivateIpAddressSpecification]
$sel:privateIpAddress:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Text
$sel:ipv6Prefixes:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [Ipv6PrefixSpecificationRequest]
$sel:ipv6PrefixCount:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Int
$sel:ipv6Addresses:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [InstanceIpv6Address]
$sel:ipv6AddressCount:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Int
$sel:ipv4Prefixes:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [Ipv4PrefixSpecificationRequest]
$sel:ipv4PrefixCount:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Int
$sel:interfaceType:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe NetworkInterfaceCreationType
$sel:groups:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [Text]
$sel:dryRun:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Bool
$sel:description:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Text
$sel:clientToken:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
groups
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NetworkInterfaceCreationType
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 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 [TagSpecification]
tagSpecifications
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
subnetId

instance Prelude.NFData CreateNetworkInterface where
  rnf :: CreateNetworkInterface -> ()
rnf CreateNetworkInterface' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [InstanceIpv6Address]
Maybe [Ipv4PrefixSpecificationRequest]
Maybe [Ipv6PrefixSpecificationRequest]
Maybe [PrivateIpAddressSpecification]
Maybe [TagSpecification]
Maybe Text
Maybe NetworkInterfaceCreationType
Text
subnetId :: Text
tagSpecifications :: Maybe [TagSpecification]
secondaryPrivateIpAddressCount :: Maybe Int
privateIpAddresses :: Maybe [PrivateIpAddressSpecification]
privateIpAddress :: Maybe Text
ipv6Prefixes :: Maybe [Ipv6PrefixSpecificationRequest]
ipv6PrefixCount :: Maybe Int
ipv6Addresses :: Maybe [InstanceIpv6Address]
ipv6AddressCount :: Maybe Int
ipv4Prefixes :: Maybe [Ipv4PrefixSpecificationRequest]
ipv4PrefixCount :: Maybe Int
interfaceType :: Maybe NetworkInterfaceCreationType
groups :: Maybe [Text]
dryRun :: Maybe Bool
description :: Maybe Text
clientToken :: Maybe Text
$sel:subnetId:CreateNetworkInterface' :: CreateNetworkInterface -> Text
$sel:tagSpecifications:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [TagSpecification]
$sel:secondaryPrivateIpAddressCount:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Int
$sel:privateIpAddresses:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [PrivateIpAddressSpecification]
$sel:privateIpAddress:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Text
$sel:ipv6Prefixes:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [Ipv6PrefixSpecificationRequest]
$sel:ipv6PrefixCount:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Int
$sel:ipv6Addresses:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [InstanceIpv6Address]
$sel:ipv6AddressCount:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Int
$sel:ipv4Prefixes:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [Ipv4PrefixSpecificationRequest]
$sel:ipv4PrefixCount:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Int
$sel:interfaceType:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe NetworkInterfaceCreationType
$sel:groups:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [Text]
$sel:dryRun:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Bool
$sel:description:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Text
$sel:clientToken:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      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 Bool
dryRun
      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 NetworkInterfaceCreationType
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 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 [TagSpecification]
tagSpecifications
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
subnetId

instance Data.ToHeaders CreateNetworkInterface where
  toHeaders :: CreateNetworkInterface -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery CreateNetworkInterface where
  toQuery :: CreateNetworkInterface -> QueryString
toQuery CreateNetworkInterface' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [InstanceIpv6Address]
Maybe [Ipv4PrefixSpecificationRequest]
Maybe [Ipv6PrefixSpecificationRequest]
Maybe [PrivateIpAddressSpecification]
Maybe [TagSpecification]
Maybe Text
Maybe NetworkInterfaceCreationType
Text
subnetId :: Text
tagSpecifications :: Maybe [TagSpecification]
secondaryPrivateIpAddressCount :: Maybe Int
privateIpAddresses :: Maybe [PrivateIpAddressSpecification]
privateIpAddress :: Maybe Text
ipv6Prefixes :: Maybe [Ipv6PrefixSpecificationRequest]
ipv6PrefixCount :: Maybe Int
ipv6Addresses :: Maybe [InstanceIpv6Address]
ipv6AddressCount :: Maybe Int
ipv4Prefixes :: Maybe [Ipv4PrefixSpecificationRequest]
ipv4PrefixCount :: Maybe Int
interfaceType :: Maybe NetworkInterfaceCreationType
groups :: Maybe [Text]
dryRun :: Maybe Bool
description :: Maybe Text
clientToken :: Maybe Text
$sel:subnetId:CreateNetworkInterface' :: CreateNetworkInterface -> Text
$sel:tagSpecifications:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [TagSpecification]
$sel:secondaryPrivateIpAddressCount:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Int
$sel:privateIpAddresses:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [PrivateIpAddressSpecification]
$sel:privateIpAddress:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Text
$sel:ipv6Prefixes:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [Ipv6PrefixSpecificationRequest]
$sel:ipv6PrefixCount:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Int
$sel:ipv6Addresses:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [InstanceIpv6Address]
$sel:ipv6AddressCount:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Int
$sel:ipv4Prefixes:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [Ipv4PrefixSpecificationRequest]
$sel:ipv4PrefixCount:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Int
$sel:interfaceType:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe NetworkInterfaceCreationType
$sel:groups:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe [Text]
$sel:dryRun:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Bool
$sel:description:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Text
$sel:clientToken:CreateNetworkInterface' :: CreateNetworkInterface -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"CreateNetworkInterface" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"ClientToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
clientToken,
        ByteString
"Description" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
description,
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        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 NetworkInterfaceCreationType
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
"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,
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"TagSpecification"
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [TagSpecification]
tagSpecifications
          ),
        ByteString
"SubnetId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
subnetId
      ]

-- | /See:/ 'newCreateNetworkInterfaceResponse' smart constructor.
data CreateNetworkInterfaceResponse = CreateNetworkInterfaceResponse'
  { -- | The token to use to retrieve the next page of results. This value is
    -- @null@ when there are no more results to return.
    CreateNetworkInterfaceResponse -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | Information about the network interface.
    CreateNetworkInterfaceResponse -> Maybe NetworkInterface
networkInterface :: Prelude.Maybe NetworkInterface,
    -- | The response's http status code.
    CreateNetworkInterfaceResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateNetworkInterfaceResponse
-> CreateNetworkInterfaceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateNetworkInterfaceResponse
-> CreateNetworkInterfaceResponse -> Bool
$c/= :: CreateNetworkInterfaceResponse
-> CreateNetworkInterfaceResponse -> Bool
== :: CreateNetworkInterfaceResponse
-> CreateNetworkInterfaceResponse -> Bool
$c== :: CreateNetworkInterfaceResponse
-> CreateNetworkInterfaceResponse -> Bool
Prelude.Eq, ReadPrec [CreateNetworkInterfaceResponse]
ReadPrec CreateNetworkInterfaceResponse
Int -> ReadS CreateNetworkInterfaceResponse
ReadS [CreateNetworkInterfaceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateNetworkInterfaceResponse]
$creadListPrec :: ReadPrec [CreateNetworkInterfaceResponse]
readPrec :: ReadPrec CreateNetworkInterfaceResponse
$creadPrec :: ReadPrec CreateNetworkInterfaceResponse
readList :: ReadS [CreateNetworkInterfaceResponse]
$creadList :: ReadS [CreateNetworkInterfaceResponse]
readsPrec :: Int -> ReadS CreateNetworkInterfaceResponse
$creadsPrec :: Int -> ReadS CreateNetworkInterfaceResponse
Prelude.Read, Int -> CreateNetworkInterfaceResponse -> ShowS
[CreateNetworkInterfaceResponse] -> ShowS
CreateNetworkInterfaceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateNetworkInterfaceResponse] -> ShowS
$cshowList :: [CreateNetworkInterfaceResponse] -> ShowS
show :: CreateNetworkInterfaceResponse -> String
$cshow :: CreateNetworkInterfaceResponse -> String
showsPrec :: Int -> CreateNetworkInterfaceResponse -> ShowS
$cshowsPrec :: Int -> CreateNetworkInterfaceResponse -> ShowS
Prelude.Show, forall x.
Rep CreateNetworkInterfaceResponse x
-> CreateNetworkInterfaceResponse
forall x.
CreateNetworkInterfaceResponse
-> Rep CreateNetworkInterfaceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateNetworkInterfaceResponse x
-> CreateNetworkInterfaceResponse
$cfrom :: forall x.
CreateNetworkInterfaceResponse
-> Rep CreateNetworkInterfaceResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateNetworkInterfaceResponse' 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:
--
-- 'clientToken', 'createNetworkInterfaceResponse_clientToken' - The token to use to retrieve the next page of results. This value is
-- @null@ when there are no more results to return.
--
-- 'networkInterface', 'createNetworkInterfaceResponse_networkInterface' - Information about the network interface.
--
-- 'httpStatus', 'createNetworkInterfaceResponse_httpStatus' - The response's http status code.
newCreateNetworkInterfaceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateNetworkInterfaceResponse
newCreateNetworkInterfaceResponse :: Int -> CreateNetworkInterfaceResponse
newCreateNetworkInterfaceResponse Int
pHttpStatus_ =
  CreateNetworkInterfaceResponse'
    { $sel:clientToken:CreateNetworkInterfaceResponse' :: Maybe Text
clientToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:networkInterface:CreateNetworkInterfaceResponse' :: Maybe NetworkInterface
networkInterface = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateNetworkInterfaceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The token to use to retrieve the next page of results. This value is
-- @null@ when there are no more results to return.
createNetworkInterfaceResponse_clientToken :: Lens.Lens' CreateNetworkInterfaceResponse (Prelude.Maybe Prelude.Text)
createNetworkInterfaceResponse_clientToken :: Lens' CreateNetworkInterfaceResponse (Maybe Text)
createNetworkInterfaceResponse_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNetworkInterfaceResponse' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:CreateNetworkInterfaceResponse' :: CreateNetworkInterfaceResponse -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: CreateNetworkInterfaceResponse
s@CreateNetworkInterfaceResponse' {} Maybe Text
a -> CreateNetworkInterfaceResponse
s {$sel:clientToken:CreateNetworkInterfaceResponse' :: Maybe Text
clientToken = Maybe Text
a} :: CreateNetworkInterfaceResponse)

-- | Information about the network interface.
createNetworkInterfaceResponse_networkInterface :: Lens.Lens' CreateNetworkInterfaceResponse (Prelude.Maybe NetworkInterface)
createNetworkInterfaceResponse_networkInterface :: Lens' CreateNetworkInterfaceResponse (Maybe NetworkInterface)
createNetworkInterfaceResponse_networkInterface = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNetworkInterfaceResponse' {Maybe NetworkInterface
networkInterface :: Maybe NetworkInterface
$sel:networkInterface:CreateNetworkInterfaceResponse' :: CreateNetworkInterfaceResponse -> Maybe NetworkInterface
networkInterface} -> Maybe NetworkInterface
networkInterface) (\s :: CreateNetworkInterfaceResponse
s@CreateNetworkInterfaceResponse' {} Maybe NetworkInterface
a -> CreateNetworkInterfaceResponse
s {$sel:networkInterface:CreateNetworkInterfaceResponse' :: Maybe NetworkInterface
networkInterface = Maybe NetworkInterface
a} :: CreateNetworkInterfaceResponse)

-- | The response's http status code.
createNetworkInterfaceResponse_httpStatus :: Lens.Lens' CreateNetworkInterfaceResponse Prelude.Int
createNetworkInterfaceResponse_httpStatus :: Lens' CreateNetworkInterfaceResponse Int
createNetworkInterfaceResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateNetworkInterfaceResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateNetworkInterfaceResponse' :: CreateNetworkInterfaceResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CreateNetworkInterfaceResponse
s@CreateNetworkInterfaceResponse' {} Int
a -> CreateNetworkInterfaceResponse
s {$sel:httpStatus:CreateNetworkInterfaceResponse' :: Int
httpStatus = Int
a} :: CreateNetworkInterfaceResponse)

instance
  Prelude.NFData
    CreateNetworkInterfaceResponse
  where
  rnf :: CreateNetworkInterfaceResponse -> ()
rnf CreateNetworkInterfaceResponse' {Int
Maybe Text
Maybe NetworkInterface
httpStatus :: Int
networkInterface :: Maybe NetworkInterface
clientToken :: Maybe Text
$sel:httpStatus:CreateNetworkInterfaceResponse' :: CreateNetworkInterfaceResponse -> Int
$sel:networkInterface:CreateNetworkInterfaceResponse' :: CreateNetworkInterfaceResponse -> Maybe NetworkInterface
$sel:clientToken:CreateNetworkInterfaceResponse' :: CreateNetworkInterfaceResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NetworkInterface
networkInterface
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus