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

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

-- |
-- Module      : Amazonka.EC2.DescribeInstanceAttribute
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes the specified attribute of the specified instance. You can
-- specify only one attribute at a time. Valid attribute values are:
-- @instanceType@ | @kernel@ | @ramdisk@ | @userData@ |
-- @disableApiTermination@ | @instanceInitiatedShutdownBehavior@ |
-- @rootDeviceName@ | @blockDeviceMapping@ | @productCodes@ |
-- @sourceDestCheck@ | @groupSet@ | @ebsOptimized@ | @sriovNetSupport@
module Amazonka.EC2.DescribeInstanceAttribute
  ( -- * Creating a Request
    DescribeInstanceAttribute (..),
    newDescribeInstanceAttribute,

    -- * Request Lenses
    describeInstanceAttribute_dryRun,
    describeInstanceAttribute_attribute,
    describeInstanceAttribute_instanceId,

    -- * Destructuring the Response
    DescribeInstanceAttributeResponse (..),
    newDescribeInstanceAttributeResponse,

    -- * Response Lenses
    describeInstanceAttributeResponse_blockDeviceMappings,
    describeInstanceAttributeResponse_disableApiStop,
    describeInstanceAttributeResponse_disableApiTermination,
    describeInstanceAttributeResponse_ebsOptimized,
    describeInstanceAttributeResponse_enaSupport,
    describeInstanceAttributeResponse_enclaveOptions,
    describeInstanceAttributeResponse_groups,
    describeInstanceAttributeResponse_instanceId,
    describeInstanceAttributeResponse_instanceInitiatedShutdownBehavior,
    describeInstanceAttributeResponse_instanceType,
    describeInstanceAttributeResponse_kernelId,
    describeInstanceAttributeResponse_productCodes,
    describeInstanceAttributeResponse_ramdiskId,
    describeInstanceAttributeResponse_rootDeviceName,
    describeInstanceAttributeResponse_sourceDestCheck,
    describeInstanceAttributeResponse_sriovNetSupport,
    describeInstanceAttributeResponse_userData,
    describeInstanceAttributeResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDescribeInstanceAttribute' smart constructor.
data DescribeInstanceAttribute = DescribeInstanceAttribute'
  { -- | Checks whether you have the required permissions for the action, without
    -- actually making the request, and provides an error response. If you have
    -- the required permissions, the error response is @DryRunOperation@.
    -- Otherwise, it is @UnauthorizedOperation@.
    DescribeInstanceAttribute -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The instance attribute.
    --
    -- Note: The @enaSupport@ attribute is not supported at this time.
    DescribeInstanceAttribute -> InstanceAttributeName
attribute :: InstanceAttributeName,
    -- | The ID of the instance.
    DescribeInstanceAttribute -> Text
instanceId :: Prelude.Text
  }
  deriving (DescribeInstanceAttribute -> DescribeInstanceAttribute -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeInstanceAttribute -> DescribeInstanceAttribute -> Bool
$c/= :: DescribeInstanceAttribute -> DescribeInstanceAttribute -> Bool
== :: DescribeInstanceAttribute -> DescribeInstanceAttribute -> Bool
$c== :: DescribeInstanceAttribute -> DescribeInstanceAttribute -> Bool
Prelude.Eq, ReadPrec [DescribeInstanceAttribute]
ReadPrec DescribeInstanceAttribute
Int -> ReadS DescribeInstanceAttribute
ReadS [DescribeInstanceAttribute]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeInstanceAttribute]
$creadListPrec :: ReadPrec [DescribeInstanceAttribute]
readPrec :: ReadPrec DescribeInstanceAttribute
$creadPrec :: ReadPrec DescribeInstanceAttribute
readList :: ReadS [DescribeInstanceAttribute]
$creadList :: ReadS [DescribeInstanceAttribute]
readsPrec :: Int -> ReadS DescribeInstanceAttribute
$creadsPrec :: Int -> ReadS DescribeInstanceAttribute
Prelude.Read, Int -> DescribeInstanceAttribute -> ShowS
[DescribeInstanceAttribute] -> ShowS
DescribeInstanceAttribute -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeInstanceAttribute] -> ShowS
$cshowList :: [DescribeInstanceAttribute] -> ShowS
show :: DescribeInstanceAttribute -> String
$cshow :: DescribeInstanceAttribute -> String
showsPrec :: Int -> DescribeInstanceAttribute -> ShowS
$cshowsPrec :: Int -> DescribeInstanceAttribute -> ShowS
Prelude.Show, forall x.
Rep DescribeInstanceAttribute x -> DescribeInstanceAttribute
forall x.
DescribeInstanceAttribute -> Rep DescribeInstanceAttribute x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeInstanceAttribute x -> DescribeInstanceAttribute
$cfrom :: forall x.
DescribeInstanceAttribute -> Rep DescribeInstanceAttribute x
Prelude.Generic)

-- |
-- Create a value of 'DescribeInstanceAttribute' 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:
--
-- 'dryRun', 'describeInstanceAttribute_dryRun' - Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
--
-- 'attribute', 'describeInstanceAttribute_attribute' - The instance attribute.
--
-- Note: The @enaSupport@ attribute is not supported at this time.
--
-- 'instanceId', 'describeInstanceAttribute_instanceId' - The ID of the instance.
newDescribeInstanceAttribute ::
  -- | 'attribute'
  InstanceAttributeName ->
  -- | 'instanceId'
  Prelude.Text ->
  DescribeInstanceAttribute
newDescribeInstanceAttribute :: InstanceAttributeName -> Text -> DescribeInstanceAttribute
newDescribeInstanceAttribute InstanceAttributeName
pAttribute_ Text
pInstanceId_ =
  DescribeInstanceAttribute'
    { $sel:dryRun:DescribeInstanceAttribute' :: Maybe Bool
dryRun =
        forall a. Maybe a
Prelude.Nothing,
      $sel:attribute:DescribeInstanceAttribute' :: InstanceAttributeName
attribute = InstanceAttributeName
pAttribute_,
      $sel:instanceId:DescribeInstanceAttribute' :: Text
instanceId = Text
pInstanceId_
    }

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

-- | The instance attribute.
--
-- Note: The @enaSupport@ attribute is not supported at this time.
describeInstanceAttribute_attribute :: Lens.Lens' DescribeInstanceAttribute InstanceAttributeName
describeInstanceAttribute_attribute :: Lens' DescribeInstanceAttribute InstanceAttributeName
describeInstanceAttribute_attribute = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInstanceAttribute' {InstanceAttributeName
attribute :: InstanceAttributeName
$sel:attribute:DescribeInstanceAttribute' :: DescribeInstanceAttribute -> InstanceAttributeName
attribute} -> InstanceAttributeName
attribute) (\s :: DescribeInstanceAttribute
s@DescribeInstanceAttribute' {} InstanceAttributeName
a -> DescribeInstanceAttribute
s {$sel:attribute:DescribeInstanceAttribute' :: InstanceAttributeName
attribute = InstanceAttributeName
a} :: DescribeInstanceAttribute)

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

instance Core.AWSRequest DescribeInstanceAttribute where
  type
    AWSResponse DescribeInstanceAttribute =
      DescribeInstanceAttributeResponse
  request :: (Service -> Service)
-> DescribeInstanceAttribute -> Request DescribeInstanceAttribute
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeInstanceAttribute
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeInstanceAttribute)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe [InstanceBlockDeviceMapping]
-> Maybe AttributeBooleanValue
-> Maybe AttributeBooleanValue
-> Maybe AttributeBooleanValue
-> Maybe AttributeBooleanValue
-> Maybe EnclaveOptions
-> Maybe [GroupIdentifier]
-> Maybe Text
-> Maybe AttributeValue
-> Maybe AttributeValue
-> Maybe AttributeValue
-> Maybe [ProductCode]
-> Maybe AttributeValue
-> Maybe AttributeValue
-> Maybe AttributeBooleanValue
-> Maybe AttributeValue
-> Maybe AttributeValue
-> Int
-> DescribeInstanceAttributeResponse
DescribeInstanceAttributeResponse'
            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
"disableApiStop")
            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
"disableApiTermination")
            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
"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
"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
"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 (Maybe a)
Data..@? Text
"instanceInitiatedShutdownBehavior")
            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
"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 (Maybe a)
Data..@? Text
"kernel")
            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
"ramdisk")
            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
"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
"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
"userData")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable DescribeInstanceAttribute where
  hashWithSalt :: Int -> DescribeInstanceAttribute -> Int
hashWithSalt Int
_salt DescribeInstanceAttribute' {Maybe Bool
Text
InstanceAttributeName
instanceId :: Text
attribute :: InstanceAttributeName
dryRun :: Maybe Bool
$sel:instanceId:DescribeInstanceAttribute' :: DescribeInstanceAttribute -> Text
$sel:attribute:DescribeInstanceAttribute' :: DescribeInstanceAttribute -> InstanceAttributeName
$sel:dryRun:DescribeInstanceAttribute' :: DescribeInstanceAttribute -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` InstanceAttributeName
attribute
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId

instance Prelude.NFData DescribeInstanceAttribute where
  rnf :: DescribeInstanceAttribute -> ()
rnf DescribeInstanceAttribute' {Maybe Bool
Text
InstanceAttributeName
instanceId :: Text
attribute :: InstanceAttributeName
dryRun :: Maybe Bool
$sel:instanceId:DescribeInstanceAttribute' :: DescribeInstanceAttribute -> Text
$sel:attribute:DescribeInstanceAttribute' :: DescribeInstanceAttribute -> InstanceAttributeName
$sel:dryRun:DescribeInstanceAttribute' :: DescribeInstanceAttribute -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf InstanceAttributeName
attribute
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
instanceId

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

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

instance Data.ToQuery DescribeInstanceAttribute where
  toQuery :: DescribeInstanceAttribute -> QueryString
toQuery DescribeInstanceAttribute' {Maybe Bool
Text
InstanceAttributeName
instanceId :: Text
attribute :: InstanceAttributeName
dryRun :: Maybe Bool
$sel:instanceId:DescribeInstanceAttribute' :: DescribeInstanceAttribute -> Text
$sel:attribute:DescribeInstanceAttribute' :: DescribeInstanceAttribute -> InstanceAttributeName
$sel:dryRun:DescribeInstanceAttribute' :: DescribeInstanceAttribute -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DescribeInstanceAttribute" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        ByteString
"Attribute" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: InstanceAttributeName
attribute,
        ByteString
"InstanceId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
instanceId
      ]

-- | Describes an instance attribute.
--
-- /See:/ 'newDescribeInstanceAttributeResponse' smart constructor.
data DescribeInstanceAttributeResponse = DescribeInstanceAttributeResponse'
  { -- | The block device mapping of the instance.
    DescribeInstanceAttributeResponse
-> Maybe [InstanceBlockDeviceMapping]
blockDeviceMappings :: Prelude.Maybe [InstanceBlockDeviceMapping],
    -- | To enable the instance for Amazon Web Services Stop Protection, set this
    -- parameter to @true@; otherwise, set it to @false@.
    DescribeInstanceAttributeResponse -> Maybe AttributeBooleanValue
disableApiStop :: Prelude.Maybe AttributeBooleanValue,
    -- | If the value is @true@, you can\'t terminate the instance through the
    -- Amazon EC2 console, CLI, or API; otherwise, you can.
    DescribeInstanceAttributeResponse -> Maybe AttributeBooleanValue
disableApiTermination :: Prelude.Maybe AttributeBooleanValue,
    -- | Indicates whether the instance is optimized for Amazon EBS I\/O.
    DescribeInstanceAttributeResponse -> Maybe AttributeBooleanValue
ebsOptimized :: Prelude.Maybe AttributeBooleanValue,
    -- | Indicates whether enhanced networking with ENA is enabled.
    DescribeInstanceAttributeResponse -> Maybe AttributeBooleanValue
enaSupport :: Prelude.Maybe AttributeBooleanValue,
    -- | To enable the instance for Amazon Web Services Nitro Enclaves, set this
    -- parameter to @true@; otherwise, set it to @false@.
    DescribeInstanceAttributeResponse -> Maybe EnclaveOptions
enclaveOptions :: Prelude.Maybe EnclaveOptions,
    -- | The security groups associated with the instance.
    DescribeInstanceAttributeResponse -> Maybe [GroupIdentifier]
groups :: Prelude.Maybe [GroupIdentifier],
    -- | The ID of the instance.
    DescribeInstanceAttributeResponse -> Maybe Text
instanceId :: Prelude.Maybe Prelude.Text,
    -- | Indicates whether an instance stops or terminates when you initiate
    -- shutdown from the instance (using the operating system command for
    -- system shutdown).
    DescribeInstanceAttributeResponse -> Maybe AttributeValue
instanceInitiatedShutdownBehavior :: Prelude.Maybe AttributeValue,
    -- | The instance type.
    DescribeInstanceAttributeResponse -> Maybe AttributeValue
instanceType :: Prelude.Maybe AttributeValue,
    -- | The kernel ID.
    DescribeInstanceAttributeResponse -> Maybe AttributeValue
kernelId :: Prelude.Maybe AttributeValue,
    -- | A list of product codes.
    DescribeInstanceAttributeResponse -> Maybe [ProductCode]
productCodes :: Prelude.Maybe [ProductCode],
    -- | The RAM disk ID.
    DescribeInstanceAttributeResponse -> Maybe AttributeValue
ramdiskId :: Prelude.Maybe AttributeValue,
    -- | The device name of the root device volume (for example, @\/dev\/sda1@).
    DescribeInstanceAttributeResponse -> Maybe AttributeValue
rootDeviceName :: Prelude.Maybe AttributeValue,
    -- | Enable or disable source\/destination checks, which ensure that the
    -- instance is either the source or the destination of any traffic that it
    -- receives. If the value is @true@, source\/destination checks are
    -- enabled; otherwise, they are disabled. The default value is @true@. You
    -- must disable source\/destination checks if the instance runs services
    -- such as network address translation, routing, or firewalls.
    DescribeInstanceAttributeResponse -> Maybe AttributeBooleanValue
sourceDestCheck :: Prelude.Maybe AttributeBooleanValue,
    -- | Indicates whether enhanced networking with the Intel 82599 Virtual
    -- Function interface is enabled.
    DescribeInstanceAttributeResponse -> Maybe AttributeValue
sriovNetSupport :: Prelude.Maybe AttributeValue,
    -- | The user data.
    DescribeInstanceAttributeResponse -> Maybe AttributeValue
userData :: Prelude.Maybe AttributeValue,
    -- | The response's http status code.
    DescribeInstanceAttributeResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeInstanceAttributeResponse
-> DescribeInstanceAttributeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeInstanceAttributeResponse
-> DescribeInstanceAttributeResponse -> Bool
$c/= :: DescribeInstanceAttributeResponse
-> DescribeInstanceAttributeResponse -> Bool
== :: DescribeInstanceAttributeResponse
-> DescribeInstanceAttributeResponse -> Bool
$c== :: DescribeInstanceAttributeResponse
-> DescribeInstanceAttributeResponse -> Bool
Prelude.Eq, ReadPrec [DescribeInstanceAttributeResponse]
ReadPrec DescribeInstanceAttributeResponse
Int -> ReadS DescribeInstanceAttributeResponse
ReadS [DescribeInstanceAttributeResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeInstanceAttributeResponse]
$creadListPrec :: ReadPrec [DescribeInstanceAttributeResponse]
readPrec :: ReadPrec DescribeInstanceAttributeResponse
$creadPrec :: ReadPrec DescribeInstanceAttributeResponse
readList :: ReadS [DescribeInstanceAttributeResponse]
$creadList :: ReadS [DescribeInstanceAttributeResponse]
readsPrec :: Int -> ReadS DescribeInstanceAttributeResponse
$creadsPrec :: Int -> ReadS DescribeInstanceAttributeResponse
Prelude.Read, Int -> DescribeInstanceAttributeResponse -> ShowS
[DescribeInstanceAttributeResponse] -> ShowS
DescribeInstanceAttributeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeInstanceAttributeResponse] -> ShowS
$cshowList :: [DescribeInstanceAttributeResponse] -> ShowS
show :: DescribeInstanceAttributeResponse -> String
$cshow :: DescribeInstanceAttributeResponse -> String
showsPrec :: Int -> DescribeInstanceAttributeResponse -> ShowS
$cshowsPrec :: Int -> DescribeInstanceAttributeResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeInstanceAttributeResponse x
-> DescribeInstanceAttributeResponse
forall x.
DescribeInstanceAttributeResponse
-> Rep DescribeInstanceAttributeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeInstanceAttributeResponse x
-> DescribeInstanceAttributeResponse
$cfrom :: forall x.
DescribeInstanceAttributeResponse
-> Rep DescribeInstanceAttributeResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeInstanceAttributeResponse' 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', 'describeInstanceAttributeResponse_blockDeviceMappings' - The block device mapping of the instance.
--
-- 'disableApiStop', 'describeInstanceAttributeResponse_disableApiStop' - To enable the instance for Amazon Web Services Stop Protection, set this
-- parameter to @true@; otherwise, set it to @false@.
--
-- 'disableApiTermination', 'describeInstanceAttributeResponse_disableApiTermination' - If the value is @true@, you can\'t terminate the instance through the
-- Amazon EC2 console, CLI, or API; otherwise, you can.
--
-- 'ebsOptimized', 'describeInstanceAttributeResponse_ebsOptimized' - Indicates whether the instance is optimized for Amazon EBS I\/O.
--
-- 'enaSupport', 'describeInstanceAttributeResponse_enaSupport' - Indicates whether enhanced networking with ENA is enabled.
--
-- 'enclaveOptions', 'describeInstanceAttributeResponse_enclaveOptions' - To enable the instance for Amazon Web Services Nitro Enclaves, set this
-- parameter to @true@; otherwise, set it to @false@.
--
-- 'groups', 'describeInstanceAttributeResponse_groups' - The security groups associated with the instance.
--
-- 'instanceId', 'describeInstanceAttributeResponse_instanceId' - The ID of the instance.
--
-- 'instanceInitiatedShutdownBehavior', 'describeInstanceAttributeResponse_instanceInitiatedShutdownBehavior' - Indicates whether an instance stops or terminates when you initiate
-- shutdown from the instance (using the operating system command for
-- system shutdown).
--
-- 'instanceType', 'describeInstanceAttributeResponse_instanceType' - The instance type.
--
-- 'kernelId', 'describeInstanceAttributeResponse_kernelId' - The kernel ID.
--
-- 'productCodes', 'describeInstanceAttributeResponse_productCodes' - A list of product codes.
--
-- 'ramdiskId', 'describeInstanceAttributeResponse_ramdiskId' - The RAM disk ID.
--
-- 'rootDeviceName', 'describeInstanceAttributeResponse_rootDeviceName' - The device name of the root device volume (for example, @\/dev\/sda1@).
--
-- 'sourceDestCheck', 'describeInstanceAttributeResponse_sourceDestCheck' - Enable or disable source\/destination checks, which ensure that the
-- instance is either the source or the destination of any traffic that it
-- receives. If the value is @true@, source\/destination checks are
-- enabled; otherwise, they are disabled. The default value is @true@. You
-- must disable source\/destination checks if the instance runs services
-- such as network address translation, routing, or firewalls.
--
-- 'sriovNetSupport', 'describeInstanceAttributeResponse_sriovNetSupport' - Indicates whether enhanced networking with the Intel 82599 Virtual
-- Function interface is enabled.
--
-- 'userData', 'describeInstanceAttributeResponse_userData' - The user data.
--
-- 'httpStatus', 'describeInstanceAttributeResponse_httpStatus' - The response's http status code.
newDescribeInstanceAttributeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeInstanceAttributeResponse
newDescribeInstanceAttributeResponse :: Int -> DescribeInstanceAttributeResponse
newDescribeInstanceAttributeResponse Int
pHttpStatus_ =
  DescribeInstanceAttributeResponse'
    { $sel:blockDeviceMappings:DescribeInstanceAttributeResponse' :: Maybe [InstanceBlockDeviceMapping]
blockDeviceMappings =
        forall a. Maybe a
Prelude.Nothing,
      $sel:disableApiStop:DescribeInstanceAttributeResponse' :: Maybe AttributeBooleanValue
disableApiStop = forall a. Maybe a
Prelude.Nothing,
      $sel:disableApiTermination:DescribeInstanceAttributeResponse' :: Maybe AttributeBooleanValue
disableApiTermination = forall a. Maybe a
Prelude.Nothing,
      $sel:ebsOptimized:DescribeInstanceAttributeResponse' :: Maybe AttributeBooleanValue
ebsOptimized = forall a. Maybe a
Prelude.Nothing,
      $sel:enaSupport:DescribeInstanceAttributeResponse' :: Maybe AttributeBooleanValue
enaSupport = forall a. Maybe a
Prelude.Nothing,
      $sel:enclaveOptions:DescribeInstanceAttributeResponse' :: Maybe EnclaveOptions
enclaveOptions = forall a. Maybe a
Prelude.Nothing,
      $sel:groups:DescribeInstanceAttributeResponse' :: Maybe [GroupIdentifier]
groups = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceId:DescribeInstanceAttributeResponse' :: Maybe Text
instanceId = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceInitiatedShutdownBehavior:DescribeInstanceAttributeResponse' :: Maybe AttributeValue
instanceInitiatedShutdownBehavior =
        forall a. Maybe a
Prelude.Nothing,
      $sel:instanceType:DescribeInstanceAttributeResponse' :: Maybe AttributeValue
instanceType = forall a. Maybe a
Prelude.Nothing,
      $sel:kernelId:DescribeInstanceAttributeResponse' :: Maybe AttributeValue
kernelId = forall a. Maybe a
Prelude.Nothing,
      $sel:productCodes:DescribeInstanceAttributeResponse' :: Maybe [ProductCode]
productCodes = forall a. Maybe a
Prelude.Nothing,
      $sel:ramdiskId:DescribeInstanceAttributeResponse' :: Maybe AttributeValue
ramdiskId = forall a. Maybe a
Prelude.Nothing,
      $sel:rootDeviceName:DescribeInstanceAttributeResponse' :: Maybe AttributeValue
rootDeviceName = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceDestCheck:DescribeInstanceAttributeResponse' :: Maybe AttributeBooleanValue
sourceDestCheck = forall a. Maybe a
Prelude.Nothing,
      $sel:sriovNetSupport:DescribeInstanceAttributeResponse' :: Maybe AttributeValue
sriovNetSupport = forall a. Maybe a
Prelude.Nothing,
      $sel:userData:DescribeInstanceAttributeResponse' :: Maybe AttributeValue
userData = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeInstanceAttributeResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The block device mapping of the instance.
describeInstanceAttributeResponse_blockDeviceMappings :: Lens.Lens' DescribeInstanceAttributeResponse (Prelude.Maybe [InstanceBlockDeviceMapping])
describeInstanceAttributeResponse_blockDeviceMappings :: Lens'
  DescribeInstanceAttributeResponse
  (Maybe [InstanceBlockDeviceMapping])
describeInstanceAttributeResponse_blockDeviceMappings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInstanceAttributeResponse' {Maybe [InstanceBlockDeviceMapping]
blockDeviceMappings :: Maybe [InstanceBlockDeviceMapping]
$sel:blockDeviceMappings:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse
-> Maybe [InstanceBlockDeviceMapping]
blockDeviceMappings} -> Maybe [InstanceBlockDeviceMapping]
blockDeviceMappings) (\s :: DescribeInstanceAttributeResponse
s@DescribeInstanceAttributeResponse' {} Maybe [InstanceBlockDeviceMapping]
a -> DescribeInstanceAttributeResponse
s {$sel:blockDeviceMappings:DescribeInstanceAttributeResponse' :: Maybe [InstanceBlockDeviceMapping]
blockDeviceMappings = Maybe [InstanceBlockDeviceMapping]
a} :: DescribeInstanceAttributeResponse) 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

-- | To enable the instance for Amazon Web Services Stop Protection, set this
-- parameter to @true@; otherwise, set it to @false@.
describeInstanceAttributeResponse_disableApiStop :: Lens.Lens' DescribeInstanceAttributeResponse (Prelude.Maybe AttributeBooleanValue)
describeInstanceAttributeResponse_disableApiStop :: Lens'
  DescribeInstanceAttributeResponse (Maybe AttributeBooleanValue)
describeInstanceAttributeResponse_disableApiStop = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInstanceAttributeResponse' {Maybe AttributeBooleanValue
disableApiStop :: Maybe AttributeBooleanValue
$sel:disableApiStop:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe AttributeBooleanValue
disableApiStop} -> Maybe AttributeBooleanValue
disableApiStop) (\s :: DescribeInstanceAttributeResponse
s@DescribeInstanceAttributeResponse' {} Maybe AttributeBooleanValue
a -> DescribeInstanceAttributeResponse
s {$sel:disableApiStop:DescribeInstanceAttributeResponse' :: Maybe AttributeBooleanValue
disableApiStop = Maybe AttributeBooleanValue
a} :: DescribeInstanceAttributeResponse)

-- | If the value is @true@, you can\'t terminate the instance through the
-- Amazon EC2 console, CLI, or API; otherwise, you can.
describeInstanceAttributeResponse_disableApiTermination :: Lens.Lens' DescribeInstanceAttributeResponse (Prelude.Maybe AttributeBooleanValue)
describeInstanceAttributeResponse_disableApiTermination :: Lens'
  DescribeInstanceAttributeResponse (Maybe AttributeBooleanValue)
describeInstanceAttributeResponse_disableApiTermination = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInstanceAttributeResponse' {Maybe AttributeBooleanValue
disableApiTermination :: Maybe AttributeBooleanValue
$sel:disableApiTermination:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe AttributeBooleanValue
disableApiTermination} -> Maybe AttributeBooleanValue
disableApiTermination) (\s :: DescribeInstanceAttributeResponse
s@DescribeInstanceAttributeResponse' {} Maybe AttributeBooleanValue
a -> DescribeInstanceAttributeResponse
s {$sel:disableApiTermination:DescribeInstanceAttributeResponse' :: Maybe AttributeBooleanValue
disableApiTermination = Maybe AttributeBooleanValue
a} :: DescribeInstanceAttributeResponse)

-- | Indicates whether the instance is optimized for Amazon EBS I\/O.
describeInstanceAttributeResponse_ebsOptimized :: Lens.Lens' DescribeInstanceAttributeResponse (Prelude.Maybe AttributeBooleanValue)
describeInstanceAttributeResponse_ebsOptimized :: Lens'
  DescribeInstanceAttributeResponse (Maybe AttributeBooleanValue)
describeInstanceAttributeResponse_ebsOptimized = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInstanceAttributeResponse' {Maybe AttributeBooleanValue
ebsOptimized :: Maybe AttributeBooleanValue
$sel:ebsOptimized:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe AttributeBooleanValue
ebsOptimized} -> Maybe AttributeBooleanValue
ebsOptimized) (\s :: DescribeInstanceAttributeResponse
s@DescribeInstanceAttributeResponse' {} Maybe AttributeBooleanValue
a -> DescribeInstanceAttributeResponse
s {$sel:ebsOptimized:DescribeInstanceAttributeResponse' :: Maybe AttributeBooleanValue
ebsOptimized = Maybe AttributeBooleanValue
a} :: DescribeInstanceAttributeResponse)

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

-- | To enable the instance for Amazon Web Services Nitro Enclaves, set this
-- parameter to @true@; otherwise, set it to @false@.
describeInstanceAttributeResponse_enclaveOptions :: Lens.Lens' DescribeInstanceAttributeResponse (Prelude.Maybe EnclaveOptions)
describeInstanceAttributeResponse_enclaveOptions :: Lens' DescribeInstanceAttributeResponse (Maybe EnclaveOptions)
describeInstanceAttributeResponse_enclaveOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInstanceAttributeResponse' {Maybe EnclaveOptions
enclaveOptions :: Maybe EnclaveOptions
$sel:enclaveOptions:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe EnclaveOptions
enclaveOptions} -> Maybe EnclaveOptions
enclaveOptions) (\s :: DescribeInstanceAttributeResponse
s@DescribeInstanceAttributeResponse' {} Maybe EnclaveOptions
a -> DescribeInstanceAttributeResponse
s {$sel:enclaveOptions:DescribeInstanceAttributeResponse' :: Maybe EnclaveOptions
enclaveOptions = Maybe EnclaveOptions
a} :: DescribeInstanceAttributeResponse)

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

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

-- | Indicates whether an instance stops or terminates when you initiate
-- shutdown from the instance (using the operating system command for
-- system shutdown).
describeInstanceAttributeResponse_instanceInitiatedShutdownBehavior :: Lens.Lens' DescribeInstanceAttributeResponse (Prelude.Maybe AttributeValue)
describeInstanceAttributeResponse_instanceInitiatedShutdownBehavior :: Lens' DescribeInstanceAttributeResponse (Maybe AttributeValue)
describeInstanceAttributeResponse_instanceInitiatedShutdownBehavior = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInstanceAttributeResponse' {Maybe AttributeValue
instanceInitiatedShutdownBehavior :: Maybe AttributeValue
$sel:instanceInitiatedShutdownBehavior:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe AttributeValue
instanceInitiatedShutdownBehavior} -> Maybe AttributeValue
instanceInitiatedShutdownBehavior) (\s :: DescribeInstanceAttributeResponse
s@DescribeInstanceAttributeResponse' {} Maybe AttributeValue
a -> DescribeInstanceAttributeResponse
s {$sel:instanceInitiatedShutdownBehavior:DescribeInstanceAttributeResponse' :: Maybe AttributeValue
instanceInitiatedShutdownBehavior = Maybe AttributeValue
a} :: DescribeInstanceAttributeResponse)

-- | The instance type.
describeInstanceAttributeResponse_instanceType :: Lens.Lens' DescribeInstanceAttributeResponse (Prelude.Maybe AttributeValue)
describeInstanceAttributeResponse_instanceType :: Lens' DescribeInstanceAttributeResponse (Maybe AttributeValue)
describeInstanceAttributeResponse_instanceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInstanceAttributeResponse' {Maybe AttributeValue
instanceType :: Maybe AttributeValue
$sel:instanceType:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe AttributeValue
instanceType} -> Maybe AttributeValue
instanceType) (\s :: DescribeInstanceAttributeResponse
s@DescribeInstanceAttributeResponse' {} Maybe AttributeValue
a -> DescribeInstanceAttributeResponse
s {$sel:instanceType:DescribeInstanceAttributeResponse' :: Maybe AttributeValue
instanceType = Maybe AttributeValue
a} :: DescribeInstanceAttributeResponse)

-- | The kernel ID.
describeInstanceAttributeResponse_kernelId :: Lens.Lens' DescribeInstanceAttributeResponse (Prelude.Maybe AttributeValue)
describeInstanceAttributeResponse_kernelId :: Lens' DescribeInstanceAttributeResponse (Maybe AttributeValue)
describeInstanceAttributeResponse_kernelId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInstanceAttributeResponse' {Maybe AttributeValue
kernelId :: Maybe AttributeValue
$sel:kernelId:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe AttributeValue
kernelId} -> Maybe AttributeValue
kernelId) (\s :: DescribeInstanceAttributeResponse
s@DescribeInstanceAttributeResponse' {} Maybe AttributeValue
a -> DescribeInstanceAttributeResponse
s {$sel:kernelId:DescribeInstanceAttributeResponse' :: Maybe AttributeValue
kernelId = Maybe AttributeValue
a} :: DescribeInstanceAttributeResponse)

-- | A list of product codes.
describeInstanceAttributeResponse_productCodes :: Lens.Lens' DescribeInstanceAttributeResponse (Prelude.Maybe [ProductCode])
describeInstanceAttributeResponse_productCodes :: Lens' DescribeInstanceAttributeResponse (Maybe [ProductCode])
describeInstanceAttributeResponse_productCodes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInstanceAttributeResponse' {Maybe [ProductCode]
productCodes :: Maybe [ProductCode]
$sel:productCodes:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe [ProductCode]
productCodes} -> Maybe [ProductCode]
productCodes) (\s :: DescribeInstanceAttributeResponse
s@DescribeInstanceAttributeResponse' {} Maybe [ProductCode]
a -> DescribeInstanceAttributeResponse
s {$sel:productCodes:DescribeInstanceAttributeResponse' :: Maybe [ProductCode]
productCodes = Maybe [ProductCode]
a} :: DescribeInstanceAttributeResponse) 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 RAM disk ID.
describeInstanceAttributeResponse_ramdiskId :: Lens.Lens' DescribeInstanceAttributeResponse (Prelude.Maybe AttributeValue)
describeInstanceAttributeResponse_ramdiskId :: Lens' DescribeInstanceAttributeResponse (Maybe AttributeValue)
describeInstanceAttributeResponse_ramdiskId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInstanceAttributeResponse' {Maybe AttributeValue
ramdiskId :: Maybe AttributeValue
$sel:ramdiskId:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe AttributeValue
ramdiskId} -> Maybe AttributeValue
ramdiskId) (\s :: DescribeInstanceAttributeResponse
s@DescribeInstanceAttributeResponse' {} Maybe AttributeValue
a -> DescribeInstanceAttributeResponse
s {$sel:ramdiskId:DescribeInstanceAttributeResponse' :: Maybe AttributeValue
ramdiskId = Maybe AttributeValue
a} :: DescribeInstanceAttributeResponse)

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

-- | Enable or disable source\/destination checks, which ensure that the
-- instance is either the source or the destination of any traffic that it
-- receives. If the value is @true@, source\/destination checks are
-- enabled; otherwise, they are disabled. The default value is @true@. You
-- must disable source\/destination checks if the instance runs services
-- such as network address translation, routing, or firewalls.
describeInstanceAttributeResponse_sourceDestCheck :: Lens.Lens' DescribeInstanceAttributeResponse (Prelude.Maybe AttributeBooleanValue)
describeInstanceAttributeResponse_sourceDestCheck :: Lens'
  DescribeInstanceAttributeResponse (Maybe AttributeBooleanValue)
describeInstanceAttributeResponse_sourceDestCheck = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInstanceAttributeResponse' {Maybe AttributeBooleanValue
sourceDestCheck :: Maybe AttributeBooleanValue
$sel:sourceDestCheck:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe AttributeBooleanValue
sourceDestCheck} -> Maybe AttributeBooleanValue
sourceDestCheck) (\s :: DescribeInstanceAttributeResponse
s@DescribeInstanceAttributeResponse' {} Maybe AttributeBooleanValue
a -> DescribeInstanceAttributeResponse
s {$sel:sourceDestCheck:DescribeInstanceAttributeResponse' :: Maybe AttributeBooleanValue
sourceDestCheck = Maybe AttributeBooleanValue
a} :: DescribeInstanceAttributeResponse)

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

-- | The user data.
describeInstanceAttributeResponse_userData :: Lens.Lens' DescribeInstanceAttributeResponse (Prelude.Maybe AttributeValue)
describeInstanceAttributeResponse_userData :: Lens' DescribeInstanceAttributeResponse (Maybe AttributeValue)
describeInstanceAttributeResponse_userData = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInstanceAttributeResponse' {Maybe AttributeValue
userData :: Maybe AttributeValue
$sel:userData:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe AttributeValue
userData} -> Maybe AttributeValue
userData) (\s :: DescribeInstanceAttributeResponse
s@DescribeInstanceAttributeResponse' {} Maybe AttributeValue
a -> DescribeInstanceAttributeResponse
s {$sel:userData:DescribeInstanceAttributeResponse' :: Maybe AttributeValue
userData = Maybe AttributeValue
a} :: DescribeInstanceAttributeResponse)

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

instance
  Prelude.NFData
    DescribeInstanceAttributeResponse
  where
  rnf :: DescribeInstanceAttributeResponse -> ()
rnf DescribeInstanceAttributeResponse' {Int
Maybe [GroupIdentifier]
Maybe [InstanceBlockDeviceMapping]
Maybe [ProductCode]
Maybe Text
Maybe AttributeBooleanValue
Maybe AttributeValue
Maybe EnclaveOptions
httpStatus :: Int
userData :: Maybe AttributeValue
sriovNetSupport :: Maybe AttributeValue
sourceDestCheck :: Maybe AttributeBooleanValue
rootDeviceName :: Maybe AttributeValue
ramdiskId :: Maybe AttributeValue
productCodes :: Maybe [ProductCode]
kernelId :: Maybe AttributeValue
instanceType :: Maybe AttributeValue
instanceInitiatedShutdownBehavior :: Maybe AttributeValue
instanceId :: Maybe Text
groups :: Maybe [GroupIdentifier]
enclaveOptions :: Maybe EnclaveOptions
enaSupport :: Maybe AttributeBooleanValue
ebsOptimized :: Maybe AttributeBooleanValue
disableApiTermination :: Maybe AttributeBooleanValue
disableApiStop :: Maybe AttributeBooleanValue
blockDeviceMappings :: Maybe [InstanceBlockDeviceMapping]
$sel:httpStatus:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Int
$sel:userData:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe AttributeValue
$sel:sriovNetSupport:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe AttributeValue
$sel:sourceDestCheck:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe AttributeBooleanValue
$sel:rootDeviceName:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe AttributeValue
$sel:ramdiskId:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe AttributeValue
$sel:productCodes:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe [ProductCode]
$sel:kernelId:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe AttributeValue
$sel:instanceType:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe AttributeValue
$sel:instanceInitiatedShutdownBehavior:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe AttributeValue
$sel:instanceId:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe Text
$sel:groups:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe [GroupIdentifier]
$sel:enclaveOptions:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe EnclaveOptions
$sel:enaSupport:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe AttributeBooleanValue
$sel:ebsOptimized:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe AttributeBooleanValue
$sel:disableApiTermination:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe AttributeBooleanValue
$sel:disableApiStop:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse -> Maybe AttributeBooleanValue
$sel:blockDeviceMappings:DescribeInstanceAttributeResponse' :: DescribeInstanceAttributeResponse
-> 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 AttributeBooleanValue
disableApiStop
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AttributeBooleanValue
disableApiTermination
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AttributeBooleanValue
ebsOptimized
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AttributeBooleanValue
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 [GroupIdentifier]
groups
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
instanceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AttributeValue
instanceInitiatedShutdownBehavior
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AttributeValue
instanceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AttributeValue
kernelId
      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 AttributeValue
ramdiskId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AttributeValue
rootDeviceName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AttributeBooleanValue
sourceDestCheck
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AttributeValue
sriovNetSupport
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AttributeValue
userData
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus