{-# 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.Instance
-- 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.Instance 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.ArchitectureValues
import Amazonka.EC2.Types.BootModeValues
import Amazonka.EC2.Types.CapacityReservationSpecificationResponse
import Amazonka.EC2.Types.CpuOptions
import Amazonka.EC2.Types.DeviceType
import Amazonka.EC2.Types.ElasticGpuAssociation
import Amazonka.EC2.Types.ElasticInferenceAcceleratorAssociation
import Amazonka.EC2.Types.EnclaveOptions
import Amazonka.EC2.Types.GroupIdentifier
import Amazonka.EC2.Types.HibernationOptions
import Amazonka.EC2.Types.HypervisorType
import Amazonka.EC2.Types.IamInstanceProfile
import Amazonka.EC2.Types.InstanceBlockDeviceMapping
import Amazonka.EC2.Types.InstanceLifecycleType
import Amazonka.EC2.Types.InstanceMaintenanceOptions
import Amazonka.EC2.Types.InstanceMetadataOptionsResponse
import Amazonka.EC2.Types.InstanceNetworkInterface
import Amazonka.EC2.Types.InstanceState
import Amazonka.EC2.Types.InstanceType
import Amazonka.EC2.Types.LicenseConfiguration
import Amazonka.EC2.Types.Monitoring
import Amazonka.EC2.Types.Placement
import Amazonka.EC2.Types.PlatformValues
import Amazonka.EC2.Types.PrivateDnsNameOptionsResponse
import Amazonka.EC2.Types.ProductCode
import Amazonka.EC2.Types.StateReason
import Amazonka.EC2.Types.Tag
import Amazonka.EC2.Types.VirtualizationType
import qualified Amazonka.Prelude as Prelude

-- | Describes an instance.
--
-- /See:/ 'newInstance' smart constructor.
data Instance = Instance'
  { -- | Any block device mapping entries for the instance.
    Instance -> Maybe [InstanceBlockDeviceMapping]
blockDeviceMappings :: Prelude.Maybe [InstanceBlockDeviceMapping],
    -- | The boot mode of the instance. For more information, see
    -- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/ami-boot.html Boot modes>
    -- in the /Amazon EC2 User Guide/.
    Instance -> Maybe BootModeValues
bootMode :: Prelude.Maybe BootModeValues,
    -- | The ID of the Capacity Reservation.
    Instance -> Maybe Text
capacityReservationId :: Prelude.Maybe Prelude.Text,
    -- | Information about the Capacity Reservation targeting option.
    Instance -> Maybe CapacityReservationSpecificationResponse
capacityReservationSpecification :: Prelude.Maybe CapacityReservationSpecificationResponse,
    -- | The idempotency token you provided when you launched the instance, if
    -- applicable.
    Instance -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | The CPU options for the instance.
    Instance -> Maybe CpuOptions
cpuOptions :: Prelude.Maybe CpuOptions,
    -- | Indicates whether the instance is optimized for Amazon EBS I\/O. This
    -- optimization provides dedicated throughput to Amazon EBS and an
    -- optimized configuration stack to provide optimal I\/O performance. This
    -- optimization isn\'t available with all instance types. Additional usage
    -- charges apply when using an EBS Optimized instance.
    Instance -> Maybe Bool
ebsOptimized :: Prelude.Maybe Prelude.Bool,
    -- | The Elastic GPU associated with the instance.
    Instance -> Maybe [ElasticGpuAssociation]
elasticGpuAssociations :: Prelude.Maybe [ElasticGpuAssociation],
    -- | The elastic inference accelerator associated with the instance.
    Instance -> Maybe [ElasticInferenceAcceleratorAssociation]
elasticInferenceAcceleratorAssociations :: Prelude.Maybe [ElasticInferenceAcceleratorAssociation],
    -- | Specifies whether enhanced networking with ENA is enabled.
    Instance -> Maybe Bool
enaSupport :: Prelude.Maybe Prelude.Bool,
    -- | Indicates whether the instance is enabled for Amazon Web Services Nitro
    -- Enclaves.
    Instance -> Maybe EnclaveOptions
enclaveOptions :: Prelude.Maybe EnclaveOptions,
    -- | Indicates whether the instance is enabled for hibernation.
    Instance -> Maybe HibernationOptions
hibernationOptions :: Prelude.Maybe HibernationOptions,
    -- | The IAM instance profile associated with the instance, if applicable.
    Instance -> Maybe IamInstanceProfile
iamInstanceProfile :: Prelude.Maybe IamInstanceProfile,
    -- | Indicates whether this is a Spot Instance or a Scheduled Instance.
    Instance -> Maybe InstanceLifecycleType
instanceLifecycle :: Prelude.Maybe InstanceLifecycleType,
    -- | The IPv6 address assigned to the instance.
    Instance -> Maybe Text
ipv6Address :: Prelude.Maybe Prelude.Text,
    -- | The kernel associated with this instance, if applicable.
    Instance -> Maybe Text
kernelId :: Prelude.Maybe Prelude.Text,
    -- | The name of the key pair, if this instance was launched with an
    -- associated key pair.
    Instance -> Maybe Text
keyName :: Prelude.Maybe Prelude.Text,
    -- | The license configurations for the instance.
    Instance -> Maybe [LicenseConfiguration]
licenses :: Prelude.Maybe [LicenseConfiguration],
    -- | Provides information on the recovery and maintenance options of your
    -- instance.
    Instance -> Maybe InstanceMaintenanceOptions
maintenanceOptions :: Prelude.Maybe InstanceMaintenanceOptions,
    -- | The metadata options for the instance.
    Instance -> Maybe InstanceMetadataOptionsResponse
metadataOptions :: Prelude.Maybe InstanceMetadataOptionsResponse,
    -- | [EC2-VPC] The network interfaces for the instance.
    Instance -> Maybe [InstanceNetworkInterface]
networkInterfaces :: Prelude.Maybe [InstanceNetworkInterface],
    -- | The Amazon Resource Name (ARN) of the Outpost.
    Instance -> Maybe Text
outpostArn :: Prelude.Maybe Prelude.Text,
    -- | The value is @Windows@ for Windows instances; otherwise blank.
    Instance -> Maybe PlatformValues
platform :: Prelude.Maybe PlatformValues,
    -- | The platform details value for the instance. For more information, see
    -- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/billing-info-fields.html AMI billing information fields>
    -- in the /Amazon EC2 User Guide/.
    Instance -> Maybe Text
platformDetails :: Prelude.Maybe Prelude.Text,
    -- | (IPv4 only) The private DNS hostname name assigned to the instance. This
    -- DNS hostname can only be used inside the Amazon EC2 network. This name
    -- is not available until the instance enters the @running@ state.
    --
    -- [EC2-VPC] The Amazon-provided DNS server resolves Amazon-provided
    -- private DNS hostnames if you\'ve enabled DNS resolution and DNS
    -- hostnames in your VPC. If you are not using the Amazon-provided DNS
    -- server in your VPC, your custom domain name servers must resolve the
    -- hostname as appropriate.
    Instance -> Maybe Text
privateDnsName :: Prelude.Maybe Prelude.Text,
    -- | The options for the instance hostname.
    Instance -> Maybe PrivateDnsNameOptionsResponse
privateDnsNameOptions :: Prelude.Maybe PrivateDnsNameOptionsResponse,
    -- | The private IPv4 address assigned to the instance.
    Instance -> Maybe Text
privateIpAddress :: Prelude.Maybe Prelude.Text,
    -- | The product codes attached to this instance, if applicable.
    Instance -> Maybe [ProductCode]
productCodes :: Prelude.Maybe [ProductCode],
    -- | (IPv4 only) The public DNS name assigned to the instance. This name is
    -- not available until the instance enters the @running@ state. For
    -- EC2-VPC, this name is only available if you\'ve enabled DNS hostnames
    -- for your VPC.
    Instance -> Maybe Text
publicDnsName :: Prelude.Maybe Prelude.Text,
    -- | The public IPv4 address, or the Carrier IP address assigned to the
    -- instance, if applicable.
    --
    -- A Carrier IP address only applies to an instance launched in a subnet
    -- associated with a Wavelength Zone.
    Instance -> Maybe Text
publicIpAddress :: Prelude.Maybe Prelude.Text,
    -- | The RAM disk associated with this instance, if applicable.
    Instance -> Maybe Text
ramdiskId :: Prelude.Maybe Prelude.Text,
    -- | The device name of the root device volume (for example, @\/dev\/sda1@).
    Instance -> Maybe Text
rootDeviceName :: Prelude.Maybe Prelude.Text,
    -- | The security groups for the instance.
    Instance -> Maybe [GroupIdentifier]
securityGroups :: Prelude.Maybe [GroupIdentifier],
    -- | Indicates whether source\/destination checking is enabled.
    Instance -> Maybe Bool
sourceDestCheck :: Prelude.Maybe Prelude.Bool,
    -- | If the request is a Spot Instance request, the ID of the request.
    Instance -> Maybe Text
spotInstanceRequestId :: Prelude.Maybe Prelude.Text,
    -- | Specifies whether enhanced networking with the Intel 82599 Virtual
    -- Function interface is enabled.
    Instance -> Maybe Text
sriovNetSupport :: Prelude.Maybe Prelude.Text,
    -- | The reason for the most recent state transition.
    Instance -> Maybe StateReason
stateReason :: Prelude.Maybe StateReason,
    -- | The reason for the most recent state transition. This might be an empty
    -- string.
    Instance -> Maybe Text
stateTransitionReason :: Prelude.Maybe Prelude.Text,
    -- | [EC2-VPC] The ID of the subnet in which the instance is running.
    Instance -> Maybe Text
subnetId :: Prelude.Maybe Prelude.Text,
    -- | Any tags assigned to the instance.
    Instance -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | If the instance is configured for NitroTPM support, the value is @v2.0@.
    -- For more information, see
    -- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/nitrotpm.html NitroTPM>
    -- in the /Amazon EC2 User Guide/.
    Instance -> Maybe Text
tpmSupport :: Prelude.Maybe Prelude.Text,
    -- | The usage operation value for the instance. For more information, see
    -- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/billing-info-fields.html AMI billing information fields>
    -- in the /Amazon EC2 User Guide/.
    Instance -> Maybe Text
usageOperation :: Prelude.Maybe Prelude.Text,
    -- | The time that the usage operation was last updated.
    Instance -> Maybe ISO8601
usageOperationUpdateTime :: Prelude.Maybe Data.ISO8601,
    -- | [EC2-VPC] The ID of the VPC in which the instance is running.
    Instance -> Maybe Text
vpcId :: Prelude.Maybe Prelude.Text,
    -- | The ID of the instance.
    Instance -> Text
instanceId :: Prelude.Text,
    -- | The ID of the AMI used to launch the instance.
    Instance -> Text
imageId :: Prelude.Text,
    -- | The AMI launch index, which can be used to find this instance in the
    -- launch group.
    Instance -> Int
amiLaunchIndex :: Prelude.Int,
    -- | The instance type.
    Instance -> InstanceType
instanceType :: InstanceType,
    -- | The time the instance was launched.
    Instance -> ISO8601
launchTime :: Data.ISO8601,
    -- | The location where the instance launched, if applicable.
    Instance -> Placement
placement :: Placement,
    -- | The monitoring for the instance.
    Instance -> Monitoring
monitoring :: Monitoring,
    -- | The architecture of the image.
    Instance -> ArchitectureValues
architecture :: ArchitectureValues,
    -- | The root device type used by the AMI. The AMI can use an EBS volume or
    -- an instance store volume.
    Instance -> DeviceType
rootDeviceType :: DeviceType,
    -- | The virtualization type of the instance.
    Instance -> VirtualizationType
virtualizationType :: VirtualizationType,
    -- | The hypervisor type of the instance. The value @xen@ is used for both
    -- Xen and Nitro hypervisors.
    Instance -> HypervisorType
hypervisor :: HypervisorType,
    -- | The current state of the instance.
    Instance -> InstanceState
state :: InstanceState
  }
  deriving (Instance -> Instance -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Instance -> Instance -> Bool
$c/= :: Instance -> Instance -> Bool
== :: Instance -> Instance -> Bool
$c== :: Instance -> Instance -> Bool
Prelude.Eq, ReadPrec [Instance]
ReadPrec Instance
Int -> ReadS Instance
ReadS [Instance]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Instance]
$creadListPrec :: ReadPrec [Instance]
readPrec :: ReadPrec Instance
$creadPrec :: ReadPrec Instance
readList :: ReadS [Instance]
$creadList :: ReadS [Instance]
readsPrec :: Int -> ReadS Instance
$creadsPrec :: Int -> ReadS Instance
Prelude.Read, Int -> Instance -> ShowS
[Instance] -> ShowS
Instance -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Instance] -> ShowS
$cshowList :: [Instance] -> ShowS
show :: Instance -> String
$cshow :: Instance -> String
showsPrec :: Int -> Instance -> ShowS
$cshowsPrec :: Int -> Instance -> ShowS
Prelude.Show, forall x. Rep Instance x -> Instance
forall x. Instance -> Rep Instance x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Instance x -> Instance
$cfrom :: forall x. Instance -> Rep Instance x
Prelude.Generic)

-- |
-- Create a value of 'Instance' 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:
--
-- 'blockDeviceMappings', 'instance_blockDeviceMappings' - Any block device mapping entries for the instance.
--
-- 'bootMode', 'instance_bootMode' - The boot mode of the instance. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/ami-boot.html Boot modes>
-- in the /Amazon EC2 User Guide/.
--
-- 'capacityReservationId', 'instance_capacityReservationId' - The ID of the Capacity Reservation.
--
-- 'capacityReservationSpecification', 'instance_capacityReservationSpecification' - Information about the Capacity Reservation targeting option.
--
-- 'clientToken', 'instance_clientToken' - The idempotency token you provided when you launched the instance, if
-- applicable.
--
-- 'cpuOptions', 'instance_cpuOptions' - The CPU options for the instance.
--
-- 'ebsOptimized', 'instance_ebsOptimized' - Indicates whether the instance is optimized for Amazon EBS I\/O. This
-- optimization provides dedicated throughput to Amazon EBS and an
-- optimized configuration stack to provide optimal I\/O performance. This
-- optimization isn\'t available with all instance types. Additional usage
-- charges apply when using an EBS Optimized instance.
--
-- 'elasticGpuAssociations', 'instance_elasticGpuAssociations' - The Elastic GPU associated with the instance.
--
-- 'elasticInferenceAcceleratorAssociations', 'instance_elasticInferenceAcceleratorAssociations' - The elastic inference accelerator associated with the instance.
--
-- 'enaSupport', 'instance_enaSupport' - Specifies whether enhanced networking with ENA is enabled.
--
-- 'enclaveOptions', 'instance_enclaveOptions' - Indicates whether the instance is enabled for Amazon Web Services Nitro
-- Enclaves.
--
-- 'hibernationOptions', 'instance_hibernationOptions' - Indicates whether the instance is enabled for hibernation.
--
-- 'iamInstanceProfile', 'instance_iamInstanceProfile' - The IAM instance profile associated with the instance, if applicable.
--
-- 'instanceLifecycle', 'instance_instanceLifecycle' - Indicates whether this is a Spot Instance or a Scheduled Instance.
--
-- 'ipv6Address', 'instance_ipv6Address' - The IPv6 address assigned to the instance.
--
-- 'kernelId', 'instance_kernelId' - The kernel associated with this instance, if applicable.
--
-- 'keyName', 'instance_keyName' - The name of the key pair, if this instance was launched with an
-- associated key pair.
--
-- 'licenses', 'instance_licenses' - The license configurations for the instance.
--
-- 'maintenanceOptions', 'instance_maintenanceOptions' - Provides information on the recovery and maintenance options of your
-- instance.
--
-- 'metadataOptions', 'instance_metadataOptions' - The metadata options for the instance.
--
-- 'networkInterfaces', 'instance_networkInterfaces' - [EC2-VPC] The network interfaces for the instance.
--
-- 'outpostArn', 'instance_outpostArn' - The Amazon Resource Name (ARN) of the Outpost.
--
-- 'platform', 'instance_platform' - The value is @Windows@ for Windows instances; otherwise blank.
--
-- 'platformDetails', 'instance_platformDetails' - The platform details value for the instance. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/billing-info-fields.html AMI billing information fields>
-- in the /Amazon EC2 User Guide/.
--
-- 'privateDnsName', 'instance_privateDnsName' - (IPv4 only) The private DNS hostname name assigned to the instance. This
-- DNS hostname can only be used inside the Amazon EC2 network. This name
-- is not available until the instance enters the @running@ state.
--
-- [EC2-VPC] The Amazon-provided DNS server resolves Amazon-provided
-- private DNS hostnames if you\'ve enabled DNS resolution and DNS
-- hostnames in your VPC. If you are not using the Amazon-provided DNS
-- server in your VPC, your custom domain name servers must resolve the
-- hostname as appropriate.
--
-- 'privateDnsNameOptions', 'instance_privateDnsNameOptions' - The options for the instance hostname.
--
-- 'privateIpAddress', 'instance_privateIpAddress' - The private IPv4 address assigned to the instance.
--
-- 'productCodes', 'instance_productCodes' - The product codes attached to this instance, if applicable.
--
-- 'publicDnsName', 'instance_publicDnsName' - (IPv4 only) The public DNS name assigned to the instance. This name is
-- not available until the instance enters the @running@ state. For
-- EC2-VPC, this name is only available if you\'ve enabled DNS hostnames
-- for your VPC.
--
-- 'publicIpAddress', 'instance_publicIpAddress' - The public IPv4 address, or the Carrier IP address assigned to the
-- instance, if applicable.
--
-- A Carrier IP address only applies to an instance launched in a subnet
-- associated with a Wavelength Zone.
--
-- 'ramdiskId', 'instance_ramdiskId' - The RAM disk associated with this instance, if applicable.
--
-- 'rootDeviceName', 'instance_rootDeviceName' - The device name of the root device volume (for example, @\/dev\/sda1@).
--
-- 'securityGroups', 'instance_securityGroups' - The security groups for the instance.
--
-- 'sourceDestCheck', 'instance_sourceDestCheck' - Indicates whether source\/destination checking is enabled.
--
-- 'spotInstanceRequestId', 'instance_spotInstanceRequestId' - If the request is a Spot Instance request, the ID of the request.
--
-- 'sriovNetSupport', 'instance_sriovNetSupport' - Specifies whether enhanced networking with the Intel 82599 Virtual
-- Function interface is enabled.
--
-- 'stateReason', 'instance_stateReason' - The reason for the most recent state transition.
--
-- 'stateTransitionReason', 'instance_stateTransitionReason' - The reason for the most recent state transition. This might be an empty
-- string.
--
-- 'subnetId', 'instance_subnetId' - [EC2-VPC] The ID of the subnet in which the instance is running.
--
-- 'tags', 'instance_tags' - Any tags assigned to the instance.
--
-- 'tpmSupport', 'instance_tpmSupport' - If the instance is configured for NitroTPM support, the value is @v2.0@.
-- For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/nitrotpm.html NitroTPM>
-- in the /Amazon EC2 User Guide/.
--
-- 'usageOperation', 'instance_usageOperation' - The usage operation value for the instance. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/billing-info-fields.html AMI billing information fields>
-- in the /Amazon EC2 User Guide/.
--
-- 'usageOperationUpdateTime', 'instance_usageOperationUpdateTime' - The time that the usage operation was last updated.
--
-- 'vpcId', 'instance_vpcId' - [EC2-VPC] The ID of the VPC in which the instance is running.
--
-- 'instanceId', 'instance_instanceId' - The ID of the instance.
--
-- 'imageId', 'instance_imageId' - The ID of the AMI used to launch the instance.
--
-- 'amiLaunchIndex', 'instance_amiLaunchIndex' - The AMI launch index, which can be used to find this instance in the
-- launch group.
--
-- 'instanceType', 'instance_instanceType' - The instance type.
--
-- 'launchTime', 'instance_launchTime' - The time the instance was launched.
--
-- 'placement', 'instance_placement' - The location where the instance launched, if applicable.
--
-- 'monitoring', 'instance_monitoring' - The monitoring for the instance.
--
-- 'architecture', 'instance_architecture' - The architecture of the image.
--
-- 'rootDeviceType', 'instance_rootDeviceType' - The root device type used by the AMI. The AMI can use an EBS volume or
-- an instance store volume.
--
-- 'virtualizationType', 'instance_virtualizationType' - The virtualization type of the instance.
--
-- 'hypervisor', 'instance_hypervisor' - The hypervisor type of the instance. The value @xen@ is used for both
-- Xen and Nitro hypervisors.
--
-- 'state', 'instance_state' - The current state of the instance.
newInstance ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'imageId'
  Prelude.Text ->
  -- | 'amiLaunchIndex'
  Prelude.Int ->
  -- | 'instanceType'
  InstanceType ->
  -- | 'launchTime'
  Prelude.UTCTime ->
  -- | 'placement'
  Placement ->
  -- | 'monitoring'
  Monitoring ->
  -- | 'architecture'
  ArchitectureValues ->
  -- | 'rootDeviceType'
  DeviceType ->
  -- | 'virtualizationType'
  VirtualizationType ->
  -- | 'hypervisor'
  HypervisorType ->
  -- | 'state'
  InstanceState ->
  Instance
newInstance :: Text
-> Text
-> Int
-> InstanceType
-> UTCTime
-> Placement
-> Monitoring
-> ArchitectureValues
-> DeviceType
-> VirtualizationType
-> HypervisorType
-> InstanceState
-> Instance
newInstance
  Text
pInstanceId_
  Text
pImageId_
  Int
pAmiLaunchIndex_
  InstanceType
pInstanceType_
  UTCTime
pLaunchTime_
  Placement
pPlacement_
  Monitoring
pMonitoring_
  ArchitectureValues
pArchitecture_
  DeviceType
pRootDeviceType_
  VirtualizationType
pVirtualizationType_
  HypervisorType
pHypervisor_
  InstanceState
pState_ =
    Instance'
      { $sel:blockDeviceMappings:Instance' :: Maybe [InstanceBlockDeviceMapping]
blockDeviceMappings = forall a. Maybe a
Prelude.Nothing,
        $sel:bootMode:Instance' :: Maybe BootModeValues
bootMode = forall a. Maybe a
Prelude.Nothing,
        $sel:capacityReservationId:Instance' :: Maybe Text
capacityReservationId = forall a. Maybe a
Prelude.Nothing,
        $sel:capacityReservationSpecification:Instance' :: Maybe CapacityReservationSpecificationResponse
capacityReservationSpecification = forall a. Maybe a
Prelude.Nothing,
        $sel:clientToken:Instance' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
        $sel:cpuOptions:Instance' :: Maybe CpuOptions
cpuOptions = forall a. Maybe a
Prelude.Nothing,
        $sel:ebsOptimized:Instance' :: Maybe Bool
ebsOptimized = forall a. Maybe a
Prelude.Nothing,
        $sel:elasticGpuAssociations:Instance' :: Maybe [ElasticGpuAssociation]
elasticGpuAssociations = forall a. Maybe a
Prelude.Nothing,
        $sel:elasticInferenceAcceleratorAssociations:Instance' :: Maybe [ElasticInferenceAcceleratorAssociation]
elasticInferenceAcceleratorAssociations =
          forall a. Maybe a
Prelude.Nothing,
        $sel:enaSupport:Instance' :: Maybe Bool
enaSupport = forall a. Maybe a
Prelude.Nothing,
        $sel:enclaveOptions:Instance' :: Maybe EnclaveOptions
enclaveOptions = forall a. Maybe a
Prelude.Nothing,
        $sel:hibernationOptions:Instance' :: Maybe HibernationOptions
hibernationOptions = forall a. Maybe a
Prelude.Nothing,
        $sel:iamInstanceProfile:Instance' :: Maybe IamInstanceProfile
iamInstanceProfile = forall a. Maybe a
Prelude.Nothing,
        $sel:instanceLifecycle:Instance' :: Maybe InstanceLifecycleType
instanceLifecycle = forall a. Maybe a
Prelude.Nothing,
        $sel:ipv6Address:Instance' :: Maybe Text
ipv6Address = forall a. Maybe a
Prelude.Nothing,
        $sel:kernelId:Instance' :: Maybe Text
kernelId = forall a. Maybe a
Prelude.Nothing,
        $sel:keyName:Instance' :: Maybe Text
keyName = forall a. Maybe a
Prelude.Nothing,
        $sel:licenses:Instance' :: Maybe [LicenseConfiguration]
licenses = forall a. Maybe a
Prelude.Nothing,
        $sel:maintenanceOptions:Instance' :: Maybe InstanceMaintenanceOptions
maintenanceOptions = forall a. Maybe a
Prelude.Nothing,
        $sel:metadataOptions:Instance' :: Maybe InstanceMetadataOptionsResponse
metadataOptions = forall a. Maybe a
Prelude.Nothing,
        $sel:networkInterfaces:Instance' :: Maybe [InstanceNetworkInterface]
networkInterfaces = forall a. Maybe a
Prelude.Nothing,
        $sel:outpostArn:Instance' :: Maybe Text
outpostArn = forall a. Maybe a
Prelude.Nothing,
        $sel:platform:Instance' :: Maybe PlatformValues
platform = forall a. Maybe a
Prelude.Nothing,
        $sel:platformDetails:Instance' :: Maybe Text
platformDetails = forall a. Maybe a
Prelude.Nothing,
        $sel:privateDnsName:Instance' :: Maybe Text
privateDnsName = forall a. Maybe a
Prelude.Nothing,
        $sel:privateDnsNameOptions:Instance' :: Maybe PrivateDnsNameOptionsResponse
privateDnsNameOptions = forall a. Maybe a
Prelude.Nothing,
        $sel:privateIpAddress:Instance' :: Maybe Text
privateIpAddress = forall a. Maybe a
Prelude.Nothing,
        $sel:productCodes:Instance' :: Maybe [ProductCode]
productCodes = forall a. Maybe a
Prelude.Nothing,
        $sel:publicDnsName:Instance' :: Maybe Text
publicDnsName = forall a. Maybe a
Prelude.Nothing,
        $sel:publicIpAddress:Instance' :: Maybe Text
publicIpAddress = forall a. Maybe a
Prelude.Nothing,
        $sel:ramdiskId:Instance' :: Maybe Text
ramdiskId = forall a. Maybe a
Prelude.Nothing,
        $sel:rootDeviceName:Instance' :: Maybe Text
rootDeviceName = forall a. Maybe a
Prelude.Nothing,
        $sel:securityGroups:Instance' :: Maybe [GroupIdentifier]
securityGroups = forall a. Maybe a
Prelude.Nothing,
        $sel:sourceDestCheck:Instance' :: Maybe Bool
sourceDestCheck = forall a. Maybe a
Prelude.Nothing,
        $sel:spotInstanceRequestId:Instance' :: Maybe Text
spotInstanceRequestId = forall a. Maybe a
Prelude.Nothing,
        $sel:sriovNetSupport:Instance' :: Maybe Text
sriovNetSupport = forall a. Maybe a
Prelude.Nothing,
        $sel:stateReason:Instance' :: Maybe StateReason
stateReason = forall a. Maybe a
Prelude.Nothing,
        $sel:stateTransitionReason:Instance' :: Maybe Text
stateTransitionReason = forall a. Maybe a
Prelude.Nothing,
        $sel:subnetId:Instance' :: Maybe Text
subnetId = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:Instance' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:tpmSupport:Instance' :: Maybe Text
tpmSupport = forall a. Maybe a
Prelude.Nothing,
        $sel:usageOperation:Instance' :: Maybe Text
usageOperation = forall a. Maybe a
Prelude.Nothing,
        $sel:usageOperationUpdateTime:Instance' :: Maybe ISO8601
usageOperationUpdateTime = forall a. Maybe a
Prelude.Nothing,
        $sel:vpcId:Instance' :: Maybe Text
vpcId = forall a. Maybe a
Prelude.Nothing,
        $sel:instanceId:Instance' :: Text
instanceId = Text
pInstanceId_,
        $sel:imageId:Instance' :: Text
imageId = Text
pImageId_,
        $sel:amiLaunchIndex:Instance' :: Int
amiLaunchIndex = Int
pAmiLaunchIndex_,
        $sel:instanceType:Instance' :: InstanceType
instanceType = InstanceType
pInstanceType_,
        $sel:launchTime:Instance' :: ISO8601
launchTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pLaunchTime_,
        $sel:placement:Instance' :: Placement
placement = Placement
pPlacement_,
        $sel:monitoring:Instance' :: Monitoring
monitoring = Monitoring
pMonitoring_,
        $sel:architecture:Instance' :: ArchitectureValues
architecture = ArchitectureValues
pArchitecture_,
        $sel:rootDeviceType:Instance' :: DeviceType
rootDeviceType = DeviceType
pRootDeviceType_,
        $sel:virtualizationType:Instance' :: VirtualizationType
virtualizationType = VirtualizationType
pVirtualizationType_,
        $sel:hypervisor:Instance' :: HypervisorType
hypervisor = HypervisorType
pHypervisor_,
        $sel:state:Instance' :: InstanceState
state = InstanceState
pState_
      }

-- | Any block device mapping entries for the instance.
instance_blockDeviceMappings :: Lens.Lens' Instance (Prelude.Maybe [InstanceBlockDeviceMapping])
instance_blockDeviceMappings :: Lens' Instance (Maybe [InstanceBlockDeviceMapping])
instance_blockDeviceMappings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe [InstanceBlockDeviceMapping]
blockDeviceMappings :: Maybe [InstanceBlockDeviceMapping]
$sel:blockDeviceMappings:Instance' :: Instance -> Maybe [InstanceBlockDeviceMapping]
blockDeviceMappings} -> Maybe [InstanceBlockDeviceMapping]
blockDeviceMappings) (\s :: Instance
s@Instance' {} Maybe [InstanceBlockDeviceMapping]
a -> Instance
s {$sel:blockDeviceMappings:Instance' :: Maybe [InstanceBlockDeviceMapping]
blockDeviceMappings = Maybe [InstanceBlockDeviceMapping]
a} :: Instance) 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 boot mode of the instance. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/ami-boot.html Boot modes>
-- in the /Amazon EC2 User Guide/.
instance_bootMode :: Lens.Lens' Instance (Prelude.Maybe BootModeValues)
instance_bootMode :: Lens' Instance (Maybe BootModeValues)
instance_bootMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe BootModeValues
bootMode :: Maybe BootModeValues
$sel:bootMode:Instance' :: Instance -> Maybe BootModeValues
bootMode} -> Maybe BootModeValues
bootMode) (\s :: Instance
s@Instance' {} Maybe BootModeValues
a -> Instance
s {$sel:bootMode:Instance' :: Maybe BootModeValues
bootMode = Maybe BootModeValues
a} :: Instance)

-- | The ID of the Capacity Reservation.
instance_capacityReservationId :: Lens.Lens' Instance (Prelude.Maybe Prelude.Text)
instance_capacityReservationId :: Lens' Instance (Maybe Text)
instance_capacityReservationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Text
capacityReservationId :: Maybe Text
$sel:capacityReservationId:Instance' :: Instance -> Maybe Text
capacityReservationId} -> Maybe Text
capacityReservationId) (\s :: Instance
s@Instance' {} Maybe Text
a -> Instance
s {$sel:capacityReservationId:Instance' :: Maybe Text
capacityReservationId = Maybe Text
a} :: Instance)

-- | Information about the Capacity Reservation targeting option.
instance_capacityReservationSpecification :: Lens.Lens' Instance (Prelude.Maybe CapacityReservationSpecificationResponse)
instance_capacityReservationSpecification :: Lens' Instance (Maybe CapacityReservationSpecificationResponse)
instance_capacityReservationSpecification = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe CapacityReservationSpecificationResponse
capacityReservationSpecification :: Maybe CapacityReservationSpecificationResponse
$sel:capacityReservationSpecification:Instance' :: Instance -> Maybe CapacityReservationSpecificationResponse
capacityReservationSpecification} -> Maybe CapacityReservationSpecificationResponse
capacityReservationSpecification) (\s :: Instance
s@Instance' {} Maybe CapacityReservationSpecificationResponse
a -> Instance
s {$sel:capacityReservationSpecification:Instance' :: Maybe CapacityReservationSpecificationResponse
capacityReservationSpecification = Maybe CapacityReservationSpecificationResponse
a} :: Instance)

-- | The idempotency token you provided when you launched the instance, if
-- applicable.
instance_clientToken :: Lens.Lens' Instance (Prelude.Maybe Prelude.Text)
instance_clientToken :: Lens' Instance (Maybe Text)
instance_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:Instance' :: Instance -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: Instance
s@Instance' {} Maybe Text
a -> Instance
s {$sel:clientToken:Instance' :: Maybe Text
clientToken = Maybe Text
a} :: Instance)

-- | The CPU options for the instance.
instance_cpuOptions :: Lens.Lens' Instance (Prelude.Maybe CpuOptions)
instance_cpuOptions :: Lens' Instance (Maybe CpuOptions)
instance_cpuOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe CpuOptions
cpuOptions :: Maybe CpuOptions
$sel:cpuOptions:Instance' :: Instance -> Maybe CpuOptions
cpuOptions} -> Maybe CpuOptions
cpuOptions) (\s :: Instance
s@Instance' {} Maybe CpuOptions
a -> Instance
s {$sel:cpuOptions:Instance' :: Maybe CpuOptions
cpuOptions = Maybe CpuOptions
a} :: Instance)

-- | Indicates whether the instance is optimized for Amazon EBS I\/O. This
-- optimization provides dedicated throughput to Amazon EBS and an
-- optimized configuration stack to provide optimal I\/O performance. This
-- optimization isn\'t available with all instance types. Additional usage
-- charges apply when using an EBS Optimized instance.
instance_ebsOptimized :: Lens.Lens' Instance (Prelude.Maybe Prelude.Bool)
instance_ebsOptimized :: Lens' Instance (Maybe Bool)
instance_ebsOptimized = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Bool
ebsOptimized :: Maybe Bool
$sel:ebsOptimized:Instance' :: Instance -> Maybe Bool
ebsOptimized} -> Maybe Bool
ebsOptimized) (\s :: Instance
s@Instance' {} Maybe Bool
a -> Instance
s {$sel:ebsOptimized:Instance' :: Maybe Bool
ebsOptimized = Maybe Bool
a} :: Instance)

-- | The Elastic GPU associated with the instance.
instance_elasticGpuAssociations :: Lens.Lens' Instance (Prelude.Maybe [ElasticGpuAssociation])
instance_elasticGpuAssociations :: Lens' Instance (Maybe [ElasticGpuAssociation])
instance_elasticGpuAssociations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe [ElasticGpuAssociation]
elasticGpuAssociations :: Maybe [ElasticGpuAssociation]
$sel:elasticGpuAssociations:Instance' :: Instance -> Maybe [ElasticGpuAssociation]
elasticGpuAssociations} -> Maybe [ElasticGpuAssociation]
elasticGpuAssociations) (\s :: Instance
s@Instance' {} Maybe [ElasticGpuAssociation]
a -> Instance
s {$sel:elasticGpuAssociations:Instance' :: Maybe [ElasticGpuAssociation]
elasticGpuAssociations = Maybe [ElasticGpuAssociation]
a} :: Instance) 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 elastic inference accelerator associated with the instance.
instance_elasticInferenceAcceleratorAssociations :: Lens.Lens' Instance (Prelude.Maybe [ElasticInferenceAcceleratorAssociation])
instance_elasticInferenceAcceleratorAssociations :: Lens' Instance (Maybe [ElasticInferenceAcceleratorAssociation])
instance_elasticInferenceAcceleratorAssociations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe [ElasticInferenceAcceleratorAssociation]
elasticInferenceAcceleratorAssociations :: Maybe [ElasticInferenceAcceleratorAssociation]
$sel:elasticInferenceAcceleratorAssociations:Instance' :: Instance -> Maybe [ElasticInferenceAcceleratorAssociation]
elasticInferenceAcceleratorAssociations} -> Maybe [ElasticInferenceAcceleratorAssociation]
elasticInferenceAcceleratorAssociations) (\s :: Instance
s@Instance' {} Maybe [ElasticInferenceAcceleratorAssociation]
a -> Instance
s {$sel:elasticInferenceAcceleratorAssociations:Instance' :: Maybe [ElasticInferenceAcceleratorAssociation]
elasticInferenceAcceleratorAssociations = Maybe [ElasticInferenceAcceleratorAssociation]
a} :: Instance) 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

-- | Specifies whether enhanced networking with ENA is enabled.
instance_enaSupport :: Lens.Lens' Instance (Prelude.Maybe Prelude.Bool)
instance_enaSupport :: Lens' Instance (Maybe Bool)
instance_enaSupport = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Bool
enaSupport :: Maybe Bool
$sel:enaSupport:Instance' :: Instance -> Maybe Bool
enaSupport} -> Maybe Bool
enaSupport) (\s :: Instance
s@Instance' {} Maybe Bool
a -> Instance
s {$sel:enaSupport:Instance' :: Maybe Bool
enaSupport = Maybe Bool
a} :: Instance)

-- | Indicates whether the instance is enabled for Amazon Web Services Nitro
-- Enclaves.
instance_enclaveOptions :: Lens.Lens' Instance (Prelude.Maybe EnclaveOptions)
instance_enclaveOptions :: Lens' Instance (Maybe EnclaveOptions)
instance_enclaveOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe EnclaveOptions
enclaveOptions :: Maybe EnclaveOptions
$sel:enclaveOptions:Instance' :: Instance -> Maybe EnclaveOptions
enclaveOptions} -> Maybe EnclaveOptions
enclaveOptions) (\s :: Instance
s@Instance' {} Maybe EnclaveOptions
a -> Instance
s {$sel:enclaveOptions:Instance' :: Maybe EnclaveOptions
enclaveOptions = Maybe EnclaveOptions
a} :: Instance)

-- | Indicates whether the instance is enabled for hibernation.
instance_hibernationOptions :: Lens.Lens' Instance (Prelude.Maybe HibernationOptions)
instance_hibernationOptions :: Lens' Instance (Maybe HibernationOptions)
instance_hibernationOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe HibernationOptions
hibernationOptions :: Maybe HibernationOptions
$sel:hibernationOptions:Instance' :: Instance -> Maybe HibernationOptions
hibernationOptions} -> Maybe HibernationOptions
hibernationOptions) (\s :: Instance
s@Instance' {} Maybe HibernationOptions
a -> Instance
s {$sel:hibernationOptions:Instance' :: Maybe HibernationOptions
hibernationOptions = Maybe HibernationOptions
a} :: Instance)

-- | The IAM instance profile associated with the instance, if applicable.
instance_iamInstanceProfile :: Lens.Lens' Instance (Prelude.Maybe IamInstanceProfile)
instance_iamInstanceProfile :: Lens' Instance (Maybe IamInstanceProfile)
instance_iamInstanceProfile = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe IamInstanceProfile
iamInstanceProfile :: Maybe IamInstanceProfile
$sel:iamInstanceProfile:Instance' :: Instance -> Maybe IamInstanceProfile
iamInstanceProfile} -> Maybe IamInstanceProfile
iamInstanceProfile) (\s :: Instance
s@Instance' {} Maybe IamInstanceProfile
a -> Instance
s {$sel:iamInstanceProfile:Instance' :: Maybe IamInstanceProfile
iamInstanceProfile = Maybe IamInstanceProfile
a} :: Instance)

-- | Indicates whether this is a Spot Instance or a Scheduled Instance.
instance_instanceLifecycle :: Lens.Lens' Instance (Prelude.Maybe InstanceLifecycleType)
instance_instanceLifecycle :: Lens' Instance (Maybe InstanceLifecycleType)
instance_instanceLifecycle = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe InstanceLifecycleType
instanceLifecycle :: Maybe InstanceLifecycleType
$sel:instanceLifecycle:Instance' :: Instance -> Maybe InstanceLifecycleType
instanceLifecycle} -> Maybe InstanceLifecycleType
instanceLifecycle) (\s :: Instance
s@Instance' {} Maybe InstanceLifecycleType
a -> Instance
s {$sel:instanceLifecycle:Instance' :: Maybe InstanceLifecycleType
instanceLifecycle = Maybe InstanceLifecycleType
a} :: Instance)

-- | The IPv6 address assigned to the instance.
instance_ipv6Address :: Lens.Lens' Instance (Prelude.Maybe Prelude.Text)
instance_ipv6Address :: Lens' Instance (Maybe Text)
instance_ipv6Address = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Text
ipv6Address :: Maybe Text
$sel:ipv6Address:Instance' :: Instance -> Maybe Text
ipv6Address} -> Maybe Text
ipv6Address) (\s :: Instance
s@Instance' {} Maybe Text
a -> Instance
s {$sel:ipv6Address:Instance' :: Maybe Text
ipv6Address = Maybe Text
a} :: Instance)

-- | The kernel associated with this instance, if applicable.
instance_kernelId :: Lens.Lens' Instance (Prelude.Maybe Prelude.Text)
instance_kernelId :: Lens' Instance (Maybe Text)
instance_kernelId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Text
kernelId :: Maybe Text
$sel:kernelId:Instance' :: Instance -> Maybe Text
kernelId} -> Maybe Text
kernelId) (\s :: Instance
s@Instance' {} Maybe Text
a -> Instance
s {$sel:kernelId:Instance' :: Maybe Text
kernelId = Maybe Text
a} :: Instance)

-- | The name of the key pair, if this instance was launched with an
-- associated key pair.
instance_keyName :: Lens.Lens' Instance (Prelude.Maybe Prelude.Text)
instance_keyName :: Lens' Instance (Maybe Text)
instance_keyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Text
keyName :: Maybe Text
$sel:keyName:Instance' :: Instance -> Maybe Text
keyName} -> Maybe Text
keyName) (\s :: Instance
s@Instance' {} Maybe Text
a -> Instance
s {$sel:keyName:Instance' :: Maybe Text
keyName = Maybe Text
a} :: Instance)

-- | The license configurations for the instance.
instance_licenses :: Lens.Lens' Instance (Prelude.Maybe [LicenseConfiguration])
instance_licenses :: Lens' Instance (Maybe [LicenseConfiguration])
instance_licenses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe [LicenseConfiguration]
licenses :: Maybe [LicenseConfiguration]
$sel:licenses:Instance' :: Instance -> Maybe [LicenseConfiguration]
licenses} -> Maybe [LicenseConfiguration]
licenses) (\s :: Instance
s@Instance' {} Maybe [LicenseConfiguration]
a -> Instance
s {$sel:licenses:Instance' :: Maybe [LicenseConfiguration]
licenses = Maybe [LicenseConfiguration]
a} :: Instance) 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

-- | Provides information on the recovery and maintenance options of your
-- instance.
instance_maintenanceOptions :: Lens.Lens' Instance (Prelude.Maybe InstanceMaintenanceOptions)
instance_maintenanceOptions :: Lens' Instance (Maybe InstanceMaintenanceOptions)
instance_maintenanceOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe InstanceMaintenanceOptions
maintenanceOptions :: Maybe InstanceMaintenanceOptions
$sel:maintenanceOptions:Instance' :: Instance -> Maybe InstanceMaintenanceOptions
maintenanceOptions} -> Maybe InstanceMaintenanceOptions
maintenanceOptions) (\s :: Instance
s@Instance' {} Maybe InstanceMaintenanceOptions
a -> Instance
s {$sel:maintenanceOptions:Instance' :: Maybe InstanceMaintenanceOptions
maintenanceOptions = Maybe InstanceMaintenanceOptions
a} :: Instance)

-- | The metadata options for the instance.
instance_metadataOptions :: Lens.Lens' Instance (Prelude.Maybe InstanceMetadataOptionsResponse)
instance_metadataOptions :: Lens' Instance (Maybe InstanceMetadataOptionsResponse)
instance_metadataOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe InstanceMetadataOptionsResponse
metadataOptions :: Maybe InstanceMetadataOptionsResponse
$sel:metadataOptions:Instance' :: Instance -> Maybe InstanceMetadataOptionsResponse
metadataOptions} -> Maybe InstanceMetadataOptionsResponse
metadataOptions) (\s :: Instance
s@Instance' {} Maybe InstanceMetadataOptionsResponse
a -> Instance
s {$sel:metadataOptions:Instance' :: Maybe InstanceMetadataOptionsResponse
metadataOptions = Maybe InstanceMetadataOptionsResponse
a} :: Instance)

-- | [EC2-VPC] The network interfaces for the instance.
instance_networkInterfaces :: Lens.Lens' Instance (Prelude.Maybe [InstanceNetworkInterface])
instance_networkInterfaces :: Lens' Instance (Maybe [InstanceNetworkInterface])
instance_networkInterfaces = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe [InstanceNetworkInterface]
networkInterfaces :: Maybe [InstanceNetworkInterface]
$sel:networkInterfaces:Instance' :: Instance -> Maybe [InstanceNetworkInterface]
networkInterfaces} -> Maybe [InstanceNetworkInterface]
networkInterfaces) (\s :: Instance
s@Instance' {} Maybe [InstanceNetworkInterface]
a -> Instance
s {$sel:networkInterfaces:Instance' :: Maybe [InstanceNetworkInterface]
networkInterfaces = Maybe [InstanceNetworkInterface]
a} :: Instance) 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 Amazon Resource Name (ARN) of the Outpost.
instance_outpostArn :: Lens.Lens' Instance (Prelude.Maybe Prelude.Text)
instance_outpostArn :: Lens' Instance (Maybe Text)
instance_outpostArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Text
outpostArn :: Maybe Text
$sel:outpostArn:Instance' :: Instance -> Maybe Text
outpostArn} -> Maybe Text
outpostArn) (\s :: Instance
s@Instance' {} Maybe Text
a -> Instance
s {$sel:outpostArn:Instance' :: Maybe Text
outpostArn = Maybe Text
a} :: Instance)

-- | The value is @Windows@ for Windows instances; otherwise blank.
instance_platform :: Lens.Lens' Instance (Prelude.Maybe PlatformValues)
instance_platform :: Lens' Instance (Maybe PlatformValues)
instance_platform = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe PlatformValues
platform :: Maybe PlatformValues
$sel:platform:Instance' :: Instance -> Maybe PlatformValues
platform} -> Maybe PlatformValues
platform) (\s :: Instance
s@Instance' {} Maybe PlatformValues
a -> Instance
s {$sel:platform:Instance' :: Maybe PlatformValues
platform = Maybe PlatformValues
a} :: Instance)

-- | The platform details value for the instance. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/billing-info-fields.html AMI billing information fields>
-- in the /Amazon EC2 User Guide/.
instance_platformDetails :: Lens.Lens' Instance (Prelude.Maybe Prelude.Text)
instance_platformDetails :: Lens' Instance (Maybe Text)
instance_platformDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Text
platformDetails :: Maybe Text
$sel:platformDetails:Instance' :: Instance -> Maybe Text
platformDetails} -> Maybe Text
platformDetails) (\s :: Instance
s@Instance' {} Maybe Text
a -> Instance
s {$sel:platformDetails:Instance' :: Maybe Text
platformDetails = Maybe Text
a} :: Instance)

-- | (IPv4 only) The private DNS hostname name assigned to the instance. This
-- DNS hostname can only be used inside the Amazon EC2 network. This name
-- is not available until the instance enters the @running@ state.
--
-- [EC2-VPC] The Amazon-provided DNS server resolves Amazon-provided
-- private DNS hostnames if you\'ve enabled DNS resolution and DNS
-- hostnames in your VPC. If you are not using the Amazon-provided DNS
-- server in your VPC, your custom domain name servers must resolve the
-- hostname as appropriate.
instance_privateDnsName :: Lens.Lens' Instance (Prelude.Maybe Prelude.Text)
instance_privateDnsName :: Lens' Instance (Maybe Text)
instance_privateDnsName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Text
privateDnsName :: Maybe Text
$sel:privateDnsName:Instance' :: Instance -> Maybe Text
privateDnsName} -> Maybe Text
privateDnsName) (\s :: Instance
s@Instance' {} Maybe Text
a -> Instance
s {$sel:privateDnsName:Instance' :: Maybe Text
privateDnsName = Maybe Text
a} :: Instance)

-- | The options for the instance hostname.
instance_privateDnsNameOptions :: Lens.Lens' Instance (Prelude.Maybe PrivateDnsNameOptionsResponse)
instance_privateDnsNameOptions :: Lens' Instance (Maybe PrivateDnsNameOptionsResponse)
instance_privateDnsNameOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe PrivateDnsNameOptionsResponse
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsResponse
$sel:privateDnsNameOptions:Instance' :: Instance -> Maybe PrivateDnsNameOptionsResponse
privateDnsNameOptions} -> Maybe PrivateDnsNameOptionsResponse
privateDnsNameOptions) (\s :: Instance
s@Instance' {} Maybe PrivateDnsNameOptionsResponse
a -> Instance
s {$sel:privateDnsNameOptions:Instance' :: Maybe PrivateDnsNameOptionsResponse
privateDnsNameOptions = Maybe PrivateDnsNameOptionsResponse
a} :: Instance)

-- | The private IPv4 address assigned to the instance.
instance_privateIpAddress :: Lens.Lens' Instance (Prelude.Maybe Prelude.Text)
instance_privateIpAddress :: Lens' Instance (Maybe Text)
instance_privateIpAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Text
privateIpAddress :: Maybe Text
$sel:privateIpAddress:Instance' :: Instance -> Maybe Text
privateIpAddress} -> Maybe Text
privateIpAddress) (\s :: Instance
s@Instance' {} Maybe Text
a -> Instance
s {$sel:privateIpAddress:Instance' :: Maybe Text
privateIpAddress = Maybe Text
a} :: Instance)

-- | The product codes attached to this instance, if applicable.
instance_productCodes :: Lens.Lens' Instance (Prelude.Maybe [ProductCode])
instance_productCodes :: Lens' Instance (Maybe [ProductCode])
instance_productCodes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe [ProductCode]
productCodes :: Maybe [ProductCode]
$sel:productCodes:Instance' :: Instance -> Maybe [ProductCode]
productCodes} -> Maybe [ProductCode]
productCodes) (\s :: Instance
s@Instance' {} Maybe [ProductCode]
a -> Instance
s {$sel:productCodes:Instance' :: Maybe [ProductCode]
productCodes = Maybe [ProductCode]
a} :: Instance) 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

-- | (IPv4 only) The public DNS name assigned to the instance. This name is
-- not available until the instance enters the @running@ state. For
-- EC2-VPC, this name is only available if you\'ve enabled DNS hostnames
-- for your VPC.
instance_publicDnsName :: Lens.Lens' Instance (Prelude.Maybe Prelude.Text)
instance_publicDnsName :: Lens' Instance (Maybe Text)
instance_publicDnsName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Text
publicDnsName :: Maybe Text
$sel:publicDnsName:Instance' :: Instance -> Maybe Text
publicDnsName} -> Maybe Text
publicDnsName) (\s :: Instance
s@Instance' {} Maybe Text
a -> Instance
s {$sel:publicDnsName:Instance' :: Maybe Text
publicDnsName = Maybe Text
a} :: Instance)

-- | The public IPv4 address, or the Carrier IP address assigned to the
-- instance, if applicable.
--
-- A Carrier IP address only applies to an instance launched in a subnet
-- associated with a Wavelength Zone.
instance_publicIpAddress :: Lens.Lens' Instance (Prelude.Maybe Prelude.Text)
instance_publicIpAddress :: Lens' Instance (Maybe Text)
instance_publicIpAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Text
publicIpAddress :: Maybe Text
$sel:publicIpAddress:Instance' :: Instance -> Maybe Text
publicIpAddress} -> Maybe Text
publicIpAddress) (\s :: Instance
s@Instance' {} Maybe Text
a -> Instance
s {$sel:publicIpAddress:Instance' :: Maybe Text
publicIpAddress = Maybe Text
a} :: Instance)

-- | The RAM disk associated with this instance, if applicable.
instance_ramdiskId :: Lens.Lens' Instance (Prelude.Maybe Prelude.Text)
instance_ramdiskId :: Lens' Instance (Maybe Text)
instance_ramdiskId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Text
ramdiskId :: Maybe Text
$sel:ramdiskId:Instance' :: Instance -> Maybe Text
ramdiskId} -> Maybe Text
ramdiskId) (\s :: Instance
s@Instance' {} Maybe Text
a -> Instance
s {$sel:ramdiskId:Instance' :: Maybe Text
ramdiskId = Maybe Text
a} :: Instance)

-- | The device name of the root device volume (for example, @\/dev\/sda1@).
instance_rootDeviceName :: Lens.Lens' Instance (Prelude.Maybe Prelude.Text)
instance_rootDeviceName :: Lens' Instance (Maybe Text)
instance_rootDeviceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Text
rootDeviceName :: Maybe Text
$sel:rootDeviceName:Instance' :: Instance -> Maybe Text
rootDeviceName} -> Maybe Text
rootDeviceName) (\s :: Instance
s@Instance' {} Maybe Text
a -> Instance
s {$sel:rootDeviceName:Instance' :: Maybe Text
rootDeviceName = Maybe Text
a} :: Instance)

-- | The security groups for the instance.
instance_securityGroups :: Lens.Lens' Instance (Prelude.Maybe [GroupIdentifier])
instance_securityGroups :: Lens' Instance (Maybe [GroupIdentifier])
instance_securityGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe [GroupIdentifier]
securityGroups :: Maybe [GroupIdentifier]
$sel:securityGroups:Instance' :: Instance -> Maybe [GroupIdentifier]
securityGroups} -> Maybe [GroupIdentifier]
securityGroups) (\s :: Instance
s@Instance' {} Maybe [GroupIdentifier]
a -> Instance
s {$sel:securityGroups:Instance' :: Maybe [GroupIdentifier]
securityGroups = Maybe [GroupIdentifier]
a} :: Instance) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | Indicates whether source\/destination checking is enabled.
instance_sourceDestCheck :: Lens.Lens' Instance (Prelude.Maybe Prelude.Bool)
instance_sourceDestCheck :: Lens' Instance (Maybe Bool)
instance_sourceDestCheck = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Bool
sourceDestCheck :: Maybe Bool
$sel:sourceDestCheck:Instance' :: Instance -> Maybe Bool
sourceDestCheck} -> Maybe Bool
sourceDestCheck) (\s :: Instance
s@Instance' {} Maybe Bool
a -> Instance
s {$sel:sourceDestCheck:Instance' :: Maybe Bool
sourceDestCheck = Maybe Bool
a} :: Instance)

-- | If the request is a Spot Instance request, the ID of the request.
instance_spotInstanceRequestId :: Lens.Lens' Instance (Prelude.Maybe Prelude.Text)
instance_spotInstanceRequestId :: Lens' Instance (Maybe Text)
instance_spotInstanceRequestId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Text
spotInstanceRequestId :: Maybe Text
$sel:spotInstanceRequestId:Instance' :: Instance -> Maybe Text
spotInstanceRequestId} -> Maybe Text
spotInstanceRequestId) (\s :: Instance
s@Instance' {} Maybe Text
a -> Instance
s {$sel:spotInstanceRequestId:Instance' :: Maybe Text
spotInstanceRequestId = Maybe Text
a} :: Instance)

-- | Specifies whether enhanced networking with the Intel 82599 Virtual
-- Function interface is enabled.
instance_sriovNetSupport :: Lens.Lens' Instance (Prelude.Maybe Prelude.Text)
instance_sriovNetSupport :: Lens' Instance (Maybe Text)
instance_sriovNetSupport = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Text
sriovNetSupport :: Maybe Text
$sel:sriovNetSupport:Instance' :: Instance -> Maybe Text
sriovNetSupport} -> Maybe Text
sriovNetSupport) (\s :: Instance
s@Instance' {} Maybe Text
a -> Instance
s {$sel:sriovNetSupport:Instance' :: Maybe Text
sriovNetSupport = Maybe Text
a} :: Instance)

-- | The reason for the most recent state transition.
instance_stateReason :: Lens.Lens' Instance (Prelude.Maybe StateReason)
instance_stateReason :: Lens' Instance (Maybe StateReason)
instance_stateReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe StateReason
stateReason :: Maybe StateReason
$sel:stateReason:Instance' :: Instance -> Maybe StateReason
stateReason} -> Maybe StateReason
stateReason) (\s :: Instance
s@Instance' {} Maybe StateReason
a -> Instance
s {$sel:stateReason:Instance' :: Maybe StateReason
stateReason = Maybe StateReason
a} :: Instance)

-- | The reason for the most recent state transition. This might be an empty
-- string.
instance_stateTransitionReason :: Lens.Lens' Instance (Prelude.Maybe Prelude.Text)
instance_stateTransitionReason :: Lens' Instance (Maybe Text)
instance_stateTransitionReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Text
stateTransitionReason :: Maybe Text
$sel:stateTransitionReason:Instance' :: Instance -> Maybe Text
stateTransitionReason} -> Maybe Text
stateTransitionReason) (\s :: Instance
s@Instance' {} Maybe Text
a -> Instance
s {$sel:stateTransitionReason:Instance' :: Maybe Text
stateTransitionReason = Maybe Text
a} :: Instance)

-- | [EC2-VPC] The ID of the subnet in which the instance is running.
instance_subnetId :: Lens.Lens' Instance (Prelude.Maybe Prelude.Text)
instance_subnetId :: Lens' Instance (Maybe Text)
instance_subnetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Text
subnetId :: Maybe Text
$sel:subnetId:Instance' :: Instance -> Maybe Text
subnetId} -> Maybe Text
subnetId) (\s :: Instance
s@Instance' {} Maybe Text
a -> Instance
s {$sel:subnetId:Instance' :: Maybe Text
subnetId = Maybe Text
a} :: Instance)

-- | Any tags assigned to the instance.
instance_tags :: Lens.Lens' Instance (Prelude.Maybe [Tag])
instance_tags :: Lens' Instance (Maybe [Tag])
instance_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:Instance' :: Instance -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: Instance
s@Instance' {} Maybe [Tag]
a -> Instance
s {$sel:tags:Instance' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: Instance) 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

-- | If the instance is configured for NitroTPM support, the value is @v2.0@.
-- For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/nitrotpm.html NitroTPM>
-- in the /Amazon EC2 User Guide/.
instance_tpmSupport :: Lens.Lens' Instance (Prelude.Maybe Prelude.Text)
instance_tpmSupport :: Lens' Instance (Maybe Text)
instance_tpmSupport = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Text
tpmSupport :: Maybe Text
$sel:tpmSupport:Instance' :: Instance -> Maybe Text
tpmSupport} -> Maybe Text
tpmSupport) (\s :: Instance
s@Instance' {} Maybe Text
a -> Instance
s {$sel:tpmSupport:Instance' :: Maybe Text
tpmSupport = Maybe Text
a} :: Instance)

-- | The usage operation value for the instance. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/billing-info-fields.html AMI billing information fields>
-- in the /Amazon EC2 User Guide/.
instance_usageOperation :: Lens.Lens' Instance (Prelude.Maybe Prelude.Text)
instance_usageOperation :: Lens' Instance (Maybe Text)
instance_usageOperation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Text
usageOperation :: Maybe Text
$sel:usageOperation:Instance' :: Instance -> Maybe Text
usageOperation} -> Maybe Text
usageOperation) (\s :: Instance
s@Instance' {} Maybe Text
a -> Instance
s {$sel:usageOperation:Instance' :: Maybe Text
usageOperation = Maybe Text
a} :: Instance)

-- | The time that the usage operation was last updated.
instance_usageOperationUpdateTime :: Lens.Lens' Instance (Prelude.Maybe Prelude.UTCTime)
instance_usageOperationUpdateTime :: Lens' Instance (Maybe UTCTime)
instance_usageOperationUpdateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe ISO8601
usageOperationUpdateTime :: Maybe ISO8601
$sel:usageOperationUpdateTime:Instance' :: Instance -> Maybe ISO8601
usageOperationUpdateTime} -> Maybe ISO8601
usageOperationUpdateTime) (\s :: Instance
s@Instance' {} Maybe ISO8601
a -> Instance
s {$sel:usageOperationUpdateTime:Instance' :: Maybe ISO8601
usageOperationUpdateTime = Maybe ISO8601
a} :: Instance) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | [EC2-VPC] The ID of the VPC in which the instance is running.
instance_vpcId :: Lens.Lens' Instance (Prelude.Maybe Prelude.Text)
instance_vpcId :: Lens' Instance (Maybe Text)
instance_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Maybe Text
vpcId :: Maybe Text
$sel:vpcId:Instance' :: Instance -> Maybe Text
vpcId} -> Maybe Text
vpcId) (\s :: Instance
s@Instance' {} Maybe Text
a -> Instance
s {$sel:vpcId:Instance' :: Maybe Text
vpcId = Maybe Text
a} :: Instance)

-- | The ID of the instance.
instance_instanceId :: Lens.Lens' Instance Prelude.Text
instance_instanceId :: Lens' Instance Text
instance_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Text
instanceId :: Text
$sel:instanceId:Instance' :: Instance -> Text
instanceId} -> Text
instanceId) (\s :: Instance
s@Instance' {} Text
a -> Instance
s {$sel:instanceId:Instance' :: Text
instanceId = Text
a} :: Instance)

-- | The ID of the AMI used to launch the instance.
instance_imageId :: Lens.Lens' Instance Prelude.Text
instance_imageId :: Lens' Instance Text
instance_imageId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Text
imageId :: Text
$sel:imageId:Instance' :: Instance -> Text
imageId} -> Text
imageId) (\s :: Instance
s@Instance' {} Text
a -> Instance
s {$sel:imageId:Instance' :: Text
imageId = Text
a} :: Instance)

-- | The AMI launch index, which can be used to find this instance in the
-- launch group.
instance_amiLaunchIndex :: Lens.Lens' Instance Prelude.Int
instance_amiLaunchIndex :: Lens' Instance Int
instance_amiLaunchIndex = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Int
amiLaunchIndex :: Int
$sel:amiLaunchIndex:Instance' :: Instance -> Int
amiLaunchIndex} -> Int
amiLaunchIndex) (\s :: Instance
s@Instance' {} Int
a -> Instance
s {$sel:amiLaunchIndex:Instance' :: Int
amiLaunchIndex = Int
a} :: Instance)

-- | The instance type.
instance_instanceType :: Lens.Lens' Instance InstanceType
instance_instanceType :: Lens' Instance InstanceType
instance_instanceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {InstanceType
instanceType :: InstanceType
$sel:instanceType:Instance' :: Instance -> InstanceType
instanceType} -> InstanceType
instanceType) (\s :: Instance
s@Instance' {} InstanceType
a -> Instance
s {$sel:instanceType:Instance' :: InstanceType
instanceType = InstanceType
a} :: Instance)

-- | The time the instance was launched.
instance_launchTime :: Lens.Lens' Instance Prelude.UTCTime
instance_launchTime :: Lens' Instance UTCTime
instance_launchTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {ISO8601
launchTime :: ISO8601
$sel:launchTime:Instance' :: Instance -> ISO8601
launchTime} -> ISO8601
launchTime) (\s :: Instance
s@Instance' {} ISO8601
a -> Instance
s {$sel:launchTime:Instance' :: ISO8601
launchTime = ISO8601
a} :: Instance) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The location where the instance launched, if applicable.
instance_placement :: Lens.Lens' Instance Placement
instance_placement :: Lens' Instance Placement
instance_placement = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Placement
placement :: Placement
$sel:placement:Instance' :: Instance -> Placement
placement} -> Placement
placement) (\s :: Instance
s@Instance' {} Placement
a -> Instance
s {$sel:placement:Instance' :: Placement
placement = Placement
a} :: Instance)

-- | The monitoring for the instance.
instance_monitoring :: Lens.Lens' Instance Monitoring
instance_monitoring :: Lens' Instance Monitoring
instance_monitoring = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {Monitoring
monitoring :: Monitoring
$sel:monitoring:Instance' :: Instance -> Monitoring
monitoring} -> Monitoring
monitoring) (\s :: Instance
s@Instance' {} Monitoring
a -> Instance
s {$sel:monitoring:Instance' :: Monitoring
monitoring = Monitoring
a} :: Instance)

-- | The architecture of the image.
instance_architecture :: Lens.Lens' Instance ArchitectureValues
instance_architecture :: Lens' Instance ArchitectureValues
instance_architecture = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {ArchitectureValues
architecture :: ArchitectureValues
$sel:architecture:Instance' :: Instance -> ArchitectureValues
architecture} -> ArchitectureValues
architecture) (\s :: Instance
s@Instance' {} ArchitectureValues
a -> Instance
s {$sel:architecture:Instance' :: ArchitectureValues
architecture = ArchitectureValues
a} :: Instance)

-- | The root device type used by the AMI. The AMI can use an EBS volume or
-- an instance store volume.
instance_rootDeviceType :: Lens.Lens' Instance DeviceType
instance_rootDeviceType :: Lens' Instance DeviceType
instance_rootDeviceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {DeviceType
rootDeviceType :: DeviceType
$sel:rootDeviceType:Instance' :: Instance -> DeviceType
rootDeviceType} -> DeviceType
rootDeviceType) (\s :: Instance
s@Instance' {} DeviceType
a -> Instance
s {$sel:rootDeviceType:Instance' :: DeviceType
rootDeviceType = DeviceType
a} :: Instance)

-- | The virtualization type of the instance.
instance_virtualizationType :: Lens.Lens' Instance VirtualizationType
instance_virtualizationType :: Lens' Instance VirtualizationType
instance_virtualizationType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {VirtualizationType
virtualizationType :: VirtualizationType
$sel:virtualizationType:Instance' :: Instance -> VirtualizationType
virtualizationType} -> VirtualizationType
virtualizationType) (\s :: Instance
s@Instance' {} VirtualizationType
a -> Instance
s {$sel:virtualizationType:Instance' :: VirtualizationType
virtualizationType = VirtualizationType
a} :: Instance)

-- | The hypervisor type of the instance. The value @xen@ is used for both
-- Xen and Nitro hypervisors.
instance_hypervisor :: Lens.Lens' Instance HypervisorType
instance_hypervisor :: Lens' Instance HypervisorType
instance_hypervisor = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {HypervisorType
hypervisor :: HypervisorType
$sel:hypervisor:Instance' :: Instance -> HypervisorType
hypervisor} -> HypervisorType
hypervisor) (\s :: Instance
s@Instance' {} HypervisorType
a -> Instance
s {$sel:hypervisor:Instance' :: HypervisorType
hypervisor = HypervisorType
a} :: Instance)

-- | The current state of the instance.
instance_state :: Lens.Lens' Instance InstanceState
instance_state :: Lens' Instance InstanceState
instance_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Instance' {InstanceState
state :: InstanceState
$sel:state:Instance' :: Instance -> InstanceState
state} -> InstanceState
state) (\s :: Instance
s@Instance' {} InstanceState
a -> Instance
s {$sel:state:Instance' :: InstanceState
state = InstanceState
a} :: Instance)

instance Data.FromXML Instance where
  parseXML :: [Node] -> Either String Instance
parseXML [Node]
x =
    Maybe [InstanceBlockDeviceMapping]
-> Maybe BootModeValues
-> Maybe Text
-> Maybe CapacityReservationSpecificationResponse
-> Maybe Text
-> Maybe CpuOptions
-> Maybe Bool
-> Maybe [ElasticGpuAssociation]
-> Maybe [ElasticInferenceAcceleratorAssociation]
-> Maybe Bool
-> Maybe EnclaveOptions
-> Maybe HibernationOptions
-> Maybe IamInstanceProfile
-> Maybe InstanceLifecycleType
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [LicenseConfiguration]
-> Maybe InstanceMaintenanceOptions
-> Maybe InstanceMetadataOptionsResponse
-> Maybe [InstanceNetworkInterface]
-> Maybe Text
-> Maybe PlatformValues
-> Maybe Text
-> Maybe Text
-> Maybe PrivateDnsNameOptionsResponse
-> Maybe Text
-> Maybe [ProductCode]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [GroupIdentifier]
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe StateReason
-> Maybe Text
-> Maybe Text
-> Maybe [Tag]
-> Maybe Text
-> Maybe Text
-> Maybe ISO8601
-> Maybe Text
-> Text
-> Text
-> Int
-> InstanceType
-> ISO8601
-> Placement
-> Monitoring
-> ArchitectureValues
-> DeviceType
-> VirtualizationType
-> HypervisorType
-> InstanceState
-> Instance
Instance'
      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
"blockDeviceMapping"
                      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
"bootMode")
      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
"capacityReservationId")
      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
"capacityReservationSpecification")
      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
"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
"cpuOptions")
      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
"ebsOptimized")
      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
"elasticGpuAssociationSet"
                      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
"elasticInferenceAcceleratorAssociationSet"
                      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
"enaSupport")
      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
"enclaveOptions")
      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
"hibernationOptions")
      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
"iamInstanceProfile")
      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
"instanceLifecycle")
      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
"ipv6Address")
      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
"kernelId")
      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
"keyName")
      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
"licenseSet"
                      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
"maintenanceOptions")
      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
"metadataOptions")
      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
"networkInterfaceSet"
                      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
"outpostArn")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"platform")
      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
"platformDetails")
      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
"privateDnsName")
      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
"privateDnsNameOptions")
      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
"productCodes"
                      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
"dnsName")
      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
"ipAddress")
      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
"ramdiskId")
      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
"rootDeviceName")
      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
"groupSet"
                      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
"sourceDestCheck")
      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
"spotInstanceRequestId")
      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
"sriovNetSupport")
      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
"stateReason")
      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
"reason")
      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")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"tagSet"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"tpmSupport")
      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
"usageOperation")
      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
"usageOperationUpdateTime")
      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
"vpcId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"instanceId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"imageId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"amiLaunchIndex")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"instanceType")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"launchTime")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"placement")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"monitoring")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"architecture")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"rootDeviceType")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"virtualizationType")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"hypervisor")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"instanceState")

instance Prelude.Hashable Instance where
  hashWithSalt :: Int -> Instance -> Int
hashWithSalt Int
_salt Instance' {Int
Maybe Bool
Maybe [ElasticGpuAssociation]
Maybe [ElasticInferenceAcceleratorAssociation]
Maybe [GroupIdentifier]
Maybe [InstanceBlockDeviceMapping]
Maybe [LicenseConfiguration]
Maybe [InstanceNetworkInterface]
Maybe [ProductCode]
Maybe [Tag]
Maybe Text
Maybe ISO8601
Maybe BootModeValues
Maybe CapacityReservationSpecificationResponse
Maybe CpuOptions
Maybe EnclaveOptions
Maybe HibernationOptions
Maybe IamInstanceProfile
Maybe InstanceLifecycleType
Maybe InstanceMaintenanceOptions
Maybe InstanceMetadataOptionsResponse
Maybe PlatformValues
Maybe PrivateDnsNameOptionsResponse
Maybe StateReason
Text
ISO8601
ArchitectureValues
DeviceType
HypervisorType
InstanceState
InstanceType
Monitoring
Placement
VirtualizationType
state :: InstanceState
hypervisor :: HypervisorType
virtualizationType :: VirtualizationType
rootDeviceType :: DeviceType
architecture :: ArchitectureValues
monitoring :: Monitoring
placement :: Placement
launchTime :: ISO8601
instanceType :: InstanceType
amiLaunchIndex :: Int
imageId :: Text
instanceId :: Text
vpcId :: Maybe Text
usageOperationUpdateTime :: Maybe ISO8601
usageOperation :: Maybe Text
tpmSupport :: Maybe Text
tags :: Maybe [Tag]
subnetId :: Maybe Text
stateTransitionReason :: Maybe Text
stateReason :: Maybe StateReason
sriovNetSupport :: Maybe Text
spotInstanceRequestId :: Maybe Text
sourceDestCheck :: Maybe Bool
securityGroups :: Maybe [GroupIdentifier]
rootDeviceName :: Maybe Text
ramdiskId :: Maybe Text
publicIpAddress :: Maybe Text
publicDnsName :: Maybe Text
productCodes :: Maybe [ProductCode]
privateIpAddress :: Maybe Text
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsResponse
privateDnsName :: Maybe Text
platformDetails :: Maybe Text
platform :: Maybe PlatformValues
outpostArn :: Maybe Text
networkInterfaces :: Maybe [InstanceNetworkInterface]
metadataOptions :: Maybe InstanceMetadataOptionsResponse
maintenanceOptions :: Maybe InstanceMaintenanceOptions
licenses :: Maybe [LicenseConfiguration]
keyName :: Maybe Text
kernelId :: Maybe Text
ipv6Address :: Maybe Text
instanceLifecycle :: Maybe InstanceLifecycleType
iamInstanceProfile :: Maybe IamInstanceProfile
hibernationOptions :: Maybe HibernationOptions
enclaveOptions :: Maybe EnclaveOptions
enaSupport :: Maybe Bool
elasticInferenceAcceleratorAssociations :: Maybe [ElasticInferenceAcceleratorAssociation]
elasticGpuAssociations :: Maybe [ElasticGpuAssociation]
ebsOptimized :: Maybe Bool
cpuOptions :: Maybe CpuOptions
clientToken :: Maybe Text
capacityReservationSpecification :: Maybe CapacityReservationSpecificationResponse
capacityReservationId :: Maybe Text
bootMode :: Maybe BootModeValues
blockDeviceMappings :: Maybe [InstanceBlockDeviceMapping]
$sel:state:Instance' :: Instance -> InstanceState
$sel:hypervisor:Instance' :: Instance -> HypervisorType
$sel:virtualizationType:Instance' :: Instance -> VirtualizationType
$sel:rootDeviceType:Instance' :: Instance -> DeviceType
$sel:architecture:Instance' :: Instance -> ArchitectureValues
$sel:monitoring:Instance' :: Instance -> Monitoring
$sel:placement:Instance' :: Instance -> Placement
$sel:launchTime:Instance' :: Instance -> ISO8601
$sel:instanceType:Instance' :: Instance -> InstanceType
$sel:amiLaunchIndex:Instance' :: Instance -> Int
$sel:imageId:Instance' :: Instance -> Text
$sel:instanceId:Instance' :: Instance -> Text
$sel:vpcId:Instance' :: Instance -> Maybe Text
$sel:usageOperationUpdateTime:Instance' :: Instance -> Maybe ISO8601
$sel:usageOperation:Instance' :: Instance -> Maybe Text
$sel:tpmSupport:Instance' :: Instance -> Maybe Text
$sel:tags:Instance' :: Instance -> Maybe [Tag]
$sel:subnetId:Instance' :: Instance -> Maybe Text
$sel:stateTransitionReason:Instance' :: Instance -> Maybe Text
$sel:stateReason:Instance' :: Instance -> Maybe StateReason
$sel:sriovNetSupport:Instance' :: Instance -> Maybe Text
$sel:spotInstanceRequestId:Instance' :: Instance -> Maybe Text
$sel:sourceDestCheck:Instance' :: Instance -> Maybe Bool
$sel:securityGroups:Instance' :: Instance -> Maybe [GroupIdentifier]
$sel:rootDeviceName:Instance' :: Instance -> Maybe Text
$sel:ramdiskId:Instance' :: Instance -> Maybe Text
$sel:publicIpAddress:Instance' :: Instance -> Maybe Text
$sel:publicDnsName:Instance' :: Instance -> Maybe Text
$sel:productCodes:Instance' :: Instance -> Maybe [ProductCode]
$sel:privateIpAddress:Instance' :: Instance -> Maybe Text
$sel:privateDnsNameOptions:Instance' :: Instance -> Maybe PrivateDnsNameOptionsResponse
$sel:privateDnsName:Instance' :: Instance -> Maybe Text
$sel:platformDetails:Instance' :: Instance -> Maybe Text
$sel:platform:Instance' :: Instance -> Maybe PlatformValues
$sel:outpostArn:Instance' :: Instance -> Maybe Text
$sel:networkInterfaces:Instance' :: Instance -> Maybe [InstanceNetworkInterface]
$sel:metadataOptions:Instance' :: Instance -> Maybe InstanceMetadataOptionsResponse
$sel:maintenanceOptions:Instance' :: Instance -> Maybe InstanceMaintenanceOptions
$sel:licenses:Instance' :: Instance -> Maybe [LicenseConfiguration]
$sel:keyName:Instance' :: Instance -> Maybe Text
$sel:kernelId:Instance' :: Instance -> Maybe Text
$sel:ipv6Address:Instance' :: Instance -> Maybe Text
$sel:instanceLifecycle:Instance' :: Instance -> Maybe InstanceLifecycleType
$sel:iamInstanceProfile:Instance' :: Instance -> Maybe IamInstanceProfile
$sel:hibernationOptions:Instance' :: Instance -> Maybe HibernationOptions
$sel:enclaveOptions:Instance' :: Instance -> Maybe EnclaveOptions
$sel:enaSupport:Instance' :: Instance -> Maybe Bool
$sel:elasticInferenceAcceleratorAssociations:Instance' :: Instance -> Maybe [ElasticInferenceAcceleratorAssociation]
$sel:elasticGpuAssociations:Instance' :: Instance -> Maybe [ElasticGpuAssociation]
$sel:ebsOptimized:Instance' :: Instance -> Maybe Bool
$sel:cpuOptions:Instance' :: Instance -> Maybe CpuOptions
$sel:clientToken:Instance' :: Instance -> Maybe Text
$sel:capacityReservationSpecification:Instance' :: Instance -> Maybe CapacityReservationSpecificationResponse
$sel:capacityReservationId:Instance' :: Instance -> Maybe Text
$sel:bootMode:Instance' :: Instance -> Maybe BootModeValues
$sel:blockDeviceMappings:Instance' :: Instance -> Maybe [InstanceBlockDeviceMapping]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [InstanceBlockDeviceMapping]
blockDeviceMappings
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BootModeValues
bootMode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
capacityReservationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CapacityReservationSpecificationResponse
capacityReservationSpecification
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CpuOptions
cpuOptions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
ebsOptimized
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ElasticGpuAssociation]
elasticGpuAssociations
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ElasticInferenceAcceleratorAssociation]
elasticInferenceAcceleratorAssociations
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
enaSupport
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EnclaveOptions
enclaveOptions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HibernationOptions
hibernationOptions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe IamInstanceProfile
iamInstanceProfile
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InstanceLifecycleType
instanceLifecycle
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ipv6Address
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
kernelId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
keyName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [LicenseConfiguration]
licenses
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InstanceMaintenanceOptions
maintenanceOptions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InstanceMetadataOptionsResponse
metadataOptions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [InstanceNetworkInterface]
networkInterfaces
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
outpostArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PlatformValues
platform
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
platformDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
privateDnsName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PrivateDnsNameOptionsResponse
privateDnsNameOptions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
privateIpAddress
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ProductCode]
productCodes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
publicDnsName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
publicIpAddress
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ramdiskId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
rootDeviceName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [GroupIdentifier]
securityGroups
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
sourceDestCheck
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
spotInstanceRequestId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sriovNetSupport
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StateReason
stateReason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
stateTransitionReason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
subnetId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
tpmSupport
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
usageOperation
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
usageOperationUpdateTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vpcId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
imageId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Int
amiLaunchIndex
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` InstanceType
instanceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ISO8601
launchTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Placement
placement
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Monitoring
monitoring
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ArchitectureValues
architecture
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` DeviceType
rootDeviceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` VirtualizationType
virtualizationType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` HypervisorType
hypervisor
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` InstanceState
state

instance Prelude.NFData Instance where
  rnf :: Instance -> ()
rnf Instance' {Int
Maybe Bool
Maybe [ElasticGpuAssociation]
Maybe [ElasticInferenceAcceleratorAssociation]
Maybe [GroupIdentifier]
Maybe [InstanceBlockDeviceMapping]
Maybe [LicenseConfiguration]
Maybe [InstanceNetworkInterface]
Maybe [ProductCode]
Maybe [Tag]
Maybe Text
Maybe ISO8601
Maybe BootModeValues
Maybe CapacityReservationSpecificationResponse
Maybe CpuOptions
Maybe EnclaveOptions
Maybe HibernationOptions
Maybe IamInstanceProfile
Maybe InstanceLifecycleType
Maybe InstanceMaintenanceOptions
Maybe InstanceMetadataOptionsResponse
Maybe PlatformValues
Maybe PrivateDnsNameOptionsResponse
Maybe StateReason
Text
ISO8601
ArchitectureValues
DeviceType
HypervisorType
InstanceState
InstanceType
Monitoring
Placement
VirtualizationType
state :: InstanceState
hypervisor :: HypervisorType
virtualizationType :: VirtualizationType
rootDeviceType :: DeviceType
architecture :: ArchitectureValues
monitoring :: Monitoring
placement :: Placement
launchTime :: ISO8601
instanceType :: InstanceType
amiLaunchIndex :: Int
imageId :: Text
instanceId :: Text
vpcId :: Maybe Text
usageOperationUpdateTime :: Maybe ISO8601
usageOperation :: Maybe Text
tpmSupport :: Maybe Text
tags :: Maybe [Tag]
subnetId :: Maybe Text
stateTransitionReason :: Maybe Text
stateReason :: Maybe StateReason
sriovNetSupport :: Maybe Text
spotInstanceRequestId :: Maybe Text
sourceDestCheck :: Maybe Bool
securityGroups :: Maybe [GroupIdentifier]
rootDeviceName :: Maybe Text
ramdiskId :: Maybe Text
publicIpAddress :: Maybe Text
publicDnsName :: Maybe Text
productCodes :: Maybe [ProductCode]
privateIpAddress :: Maybe Text
privateDnsNameOptions :: Maybe PrivateDnsNameOptionsResponse
privateDnsName :: Maybe Text
platformDetails :: Maybe Text
platform :: Maybe PlatformValues
outpostArn :: Maybe Text
networkInterfaces :: Maybe [InstanceNetworkInterface]
metadataOptions :: Maybe InstanceMetadataOptionsResponse
maintenanceOptions :: Maybe InstanceMaintenanceOptions
licenses :: Maybe [LicenseConfiguration]
keyName :: Maybe Text
kernelId :: Maybe Text
ipv6Address :: Maybe Text
instanceLifecycle :: Maybe InstanceLifecycleType
iamInstanceProfile :: Maybe IamInstanceProfile
hibernationOptions :: Maybe HibernationOptions
enclaveOptions :: Maybe EnclaveOptions
enaSupport :: Maybe Bool
elasticInferenceAcceleratorAssociations :: Maybe [ElasticInferenceAcceleratorAssociation]
elasticGpuAssociations :: Maybe [ElasticGpuAssociation]
ebsOptimized :: Maybe Bool
cpuOptions :: Maybe CpuOptions
clientToken :: Maybe Text
capacityReservationSpecification :: Maybe CapacityReservationSpecificationResponse
capacityReservationId :: Maybe Text
bootMode :: Maybe BootModeValues
blockDeviceMappings :: Maybe [InstanceBlockDeviceMapping]
$sel:state:Instance' :: Instance -> InstanceState
$sel:hypervisor:Instance' :: Instance -> HypervisorType
$sel:virtualizationType:Instance' :: Instance -> VirtualizationType
$sel:rootDeviceType:Instance' :: Instance -> DeviceType
$sel:architecture:Instance' :: Instance -> ArchitectureValues
$sel:monitoring:Instance' :: Instance -> Monitoring
$sel:placement:Instance' :: Instance -> Placement
$sel:launchTime:Instance' :: Instance -> ISO8601
$sel:instanceType:Instance' :: Instance -> InstanceType
$sel:amiLaunchIndex:Instance' :: Instance -> Int
$sel:imageId:Instance' :: Instance -> Text
$sel:instanceId:Instance' :: Instance -> Text
$sel:vpcId:Instance' :: Instance -> Maybe Text
$sel:usageOperationUpdateTime:Instance' :: Instance -> Maybe ISO8601
$sel:usageOperation:Instance' :: Instance -> Maybe Text
$sel:tpmSupport:Instance' :: Instance -> Maybe Text
$sel:tags:Instance' :: Instance -> Maybe [Tag]
$sel:subnetId:Instance' :: Instance -> Maybe Text
$sel:stateTransitionReason:Instance' :: Instance -> Maybe Text
$sel:stateReason:Instance' :: Instance -> Maybe StateReason
$sel:sriovNetSupport:Instance' :: Instance -> Maybe Text
$sel:spotInstanceRequestId:Instance' :: Instance -> Maybe Text
$sel:sourceDestCheck:Instance' :: Instance -> Maybe Bool
$sel:securityGroups:Instance' :: Instance -> Maybe [GroupIdentifier]
$sel:rootDeviceName:Instance' :: Instance -> Maybe Text
$sel:ramdiskId:Instance' :: Instance -> Maybe Text
$sel:publicIpAddress:Instance' :: Instance -> Maybe Text
$sel:publicDnsName:Instance' :: Instance -> Maybe Text
$sel:productCodes:Instance' :: Instance -> Maybe [ProductCode]
$sel:privateIpAddress:Instance' :: Instance -> Maybe Text
$sel:privateDnsNameOptions:Instance' :: Instance -> Maybe PrivateDnsNameOptionsResponse
$sel:privateDnsName:Instance' :: Instance -> Maybe Text
$sel:platformDetails:Instance' :: Instance -> Maybe Text
$sel:platform:Instance' :: Instance -> Maybe PlatformValues
$sel:outpostArn:Instance' :: Instance -> Maybe Text
$sel:networkInterfaces:Instance' :: Instance -> Maybe [InstanceNetworkInterface]
$sel:metadataOptions:Instance' :: Instance -> Maybe InstanceMetadataOptionsResponse
$sel:maintenanceOptions:Instance' :: Instance -> Maybe InstanceMaintenanceOptions
$sel:licenses:Instance' :: Instance -> Maybe [LicenseConfiguration]
$sel:keyName:Instance' :: Instance -> Maybe Text
$sel:kernelId:Instance' :: Instance -> Maybe Text
$sel:ipv6Address:Instance' :: Instance -> Maybe Text
$sel:instanceLifecycle:Instance' :: Instance -> Maybe InstanceLifecycleType
$sel:iamInstanceProfile:Instance' :: Instance -> Maybe IamInstanceProfile
$sel:hibernationOptions:Instance' :: Instance -> Maybe HibernationOptions
$sel:enclaveOptions:Instance' :: Instance -> Maybe EnclaveOptions
$sel:enaSupport:Instance' :: Instance -> Maybe Bool
$sel:elasticInferenceAcceleratorAssociations:Instance' :: Instance -> Maybe [ElasticInferenceAcceleratorAssociation]
$sel:elasticGpuAssociations:Instance' :: Instance -> Maybe [ElasticGpuAssociation]
$sel:ebsOptimized:Instance' :: Instance -> Maybe Bool
$sel:cpuOptions:Instance' :: Instance -> Maybe CpuOptions
$sel:clientToken:Instance' :: Instance -> Maybe Text
$sel:capacityReservationSpecification:Instance' :: Instance -> Maybe CapacityReservationSpecificationResponse
$sel:capacityReservationId:Instance' :: Instance -> Maybe Text
$sel:bootMode:Instance' :: Instance -> Maybe BootModeValues
$sel:blockDeviceMappings:Instance' :: Instance -> Maybe [InstanceBlockDeviceMapping]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [InstanceBlockDeviceMapping]
blockDeviceMappings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BootModeValues
bootMode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
capacityReservationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CapacityReservationSpecificationResponse
capacityReservationSpecification
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 CpuOptions
cpuOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
ebsOptimized
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ElasticGpuAssociation]
elasticGpuAssociations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ElasticInferenceAcceleratorAssociation]
elasticInferenceAcceleratorAssociations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
enaSupport
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EnclaveOptions
enclaveOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HibernationOptions
hibernationOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe IamInstanceProfile
iamInstanceProfile
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InstanceLifecycleType
instanceLifecycle
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ipv6Address
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kernelId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
keyName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [LicenseConfiguration]
licenses
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InstanceMaintenanceOptions
maintenanceOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InstanceMetadataOptionsResponse
metadataOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [InstanceNetworkInterface]
networkInterfaces
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
outpostArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PlatformValues
platform
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
platformDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
privateDnsName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe PrivateDnsNameOptionsResponse
privateDnsNameOptions
      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 [ProductCode]
productCodes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
publicDnsName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
publicIpAddress
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
ramdiskId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
rootDeviceName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [GroupIdentifier]
securityGroups
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Bool
sourceDestCheck
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
spotInstanceRequestId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
sriovNetSupport
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe StateReason
stateReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
stateTransitionReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
subnetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
tpmSupport
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
usageOperation
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe ISO8601
usageOperationUpdateTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
vpcId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Text
instanceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Text
imageId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Int
amiLaunchIndex
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        InstanceType
instanceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        ISO8601
launchTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Placement
placement
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Monitoring
monitoring
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        ArchitectureValues
architecture
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        DeviceType
rootDeviceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        VirtualizationType
virtualizationType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        HypervisorType
hypervisor
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        InstanceState
state