{-# 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.LaunchTemplateInstanceMetadataOptions
-- 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.LaunchTemplateInstanceMetadataOptions 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.LaunchTemplateHttpTokensState
import Amazonka.EC2.Types.LaunchTemplateInstanceMetadataEndpointState
import Amazonka.EC2.Types.LaunchTemplateInstanceMetadataOptionsState
import Amazonka.EC2.Types.LaunchTemplateInstanceMetadataProtocolIpv6
import Amazonka.EC2.Types.LaunchTemplateInstanceMetadataTagsState
import qualified Amazonka.Prelude as Prelude

-- | The metadata options for the instance. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/ec2-instance-metadata.html Instance metadata and user data>
-- in the /Amazon Elastic Compute Cloud User Guide/.
--
-- /See:/ 'newLaunchTemplateInstanceMetadataOptions' smart constructor.
data LaunchTemplateInstanceMetadataOptions = LaunchTemplateInstanceMetadataOptions'
  { -- | Enables or disables the HTTP metadata endpoint on your instances. If the
    -- parameter is not specified, the default state is @enabled@.
    --
    -- If you specify a value of @disabled@, you will not be able to access
    -- your instance metadata.
    LaunchTemplateInstanceMetadataOptions
-> Maybe LaunchTemplateInstanceMetadataEndpointState
httpEndpoint :: Prelude.Maybe LaunchTemplateInstanceMetadataEndpointState,
    -- | Enables or disables the IPv6 endpoint for the instance metadata service.
    --
    -- Default: @disabled@
    LaunchTemplateInstanceMetadataOptions
-> Maybe LaunchTemplateInstanceMetadataProtocolIpv6
httpProtocolIpv6 :: Prelude.Maybe LaunchTemplateInstanceMetadataProtocolIpv6,
    -- | The desired HTTP PUT response hop limit for instance metadata requests.
    -- The larger the number, the further instance metadata requests can
    -- travel.
    --
    -- Default: 1
    --
    -- Possible values: Integers from 1 to 64
    LaunchTemplateInstanceMetadataOptions -> Maybe Int
httpPutResponseHopLimit :: Prelude.Maybe Prelude.Int,
    -- | The state of token usage for your instance metadata requests. If the
    -- parameter is not specified in the request, the default state is
    -- @optional@.
    --
    -- If the state is @optional@, you can choose to retrieve instance metadata
    -- with or without a signed token header on your request. If you retrieve
    -- the IAM role credentials without a token, the version 1.0 role
    -- credentials are returned. If you retrieve the IAM role credentials using
    -- a valid signed token, the version 2.0 role credentials are returned.
    --
    -- If the state is @required@, you must send a signed token header with any
    -- instance metadata retrieval requests. In this state, retrieving the IAM
    -- role credentials always returns the version 2.0 credentials; the version
    -- 1.0 credentials are not available.
    LaunchTemplateInstanceMetadataOptions
-> Maybe LaunchTemplateHttpTokensState
httpTokens :: Prelude.Maybe LaunchTemplateHttpTokensState,
    -- | Set to @enabled@ to allow access to instance tags from the instance
    -- metadata. Set to @disabled@ to turn off access to instance tags from the
    -- instance metadata. For more information, see
    -- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/Using_Tags.html#work-with-tags-in-IMDS Work with instance tags using the instance metadata>.
    --
    -- Default: @disabled@
    LaunchTemplateInstanceMetadataOptions
-> Maybe LaunchTemplateInstanceMetadataTagsState
instanceMetadataTags :: Prelude.Maybe LaunchTemplateInstanceMetadataTagsState,
    -- | The state of the metadata option changes.
    --
    -- @pending@ - The metadata options are being updated and the instance is
    -- not ready to process metadata traffic with the new selection.
    --
    -- @applied@ - The metadata options have been successfully applied on the
    -- instance.
    LaunchTemplateInstanceMetadataOptions
-> Maybe LaunchTemplateInstanceMetadataOptionsState
state :: Prelude.Maybe LaunchTemplateInstanceMetadataOptionsState
  }
  deriving (LaunchTemplateInstanceMetadataOptions
-> LaunchTemplateInstanceMetadataOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LaunchTemplateInstanceMetadataOptions
-> LaunchTemplateInstanceMetadataOptions -> Bool
$c/= :: LaunchTemplateInstanceMetadataOptions
-> LaunchTemplateInstanceMetadataOptions -> Bool
== :: LaunchTemplateInstanceMetadataOptions
-> LaunchTemplateInstanceMetadataOptions -> Bool
$c== :: LaunchTemplateInstanceMetadataOptions
-> LaunchTemplateInstanceMetadataOptions -> Bool
Prelude.Eq, ReadPrec [LaunchTemplateInstanceMetadataOptions]
ReadPrec LaunchTemplateInstanceMetadataOptions
Int -> ReadS LaunchTemplateInstanceMetadataOptions
ReadS [LaunchTemplateInstanceMetadataOptions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LaunchTemplateInstanceMetadataOptions]
$creadListPrec :: ReadPrec [LaunchTemplateInstanceMetadataOptions]
readPrec :: ReadPrec LaunchTemplateInstanceMetadataOptions
$creadPrec :: ReadPrec LaunchTemplateInstanceMetadataOptions
readList :: ReadS [LaunchTemplateInstanceMetadataOptions]
$creadList :: ReadS [LaunchTemplateInstanceMetadataOptions]
readsPrec :: Int -> ReadS LaunchTemplateInstanceMetadataOptions
$creadsPrec :: Int -> ReadS LaunchTemplateInstanceMetadataOptions
Prelude.Read, Int -> LaunchTemplateInstanceMetadataOptions -> ShowS
[LaunchTemplateInstanceMetadataOptions] -> ShowS
LaunchTemplateInstanceMetadataOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LaunchTemplateInstanceMetadataOptions] -> ShowS
$cshowList :: [LaunchTemplateInstanceMetadataOptions] -> ShowS
show :: LaunchTemplateInstanceMetadataOptions -> String
$cshow :: LaunchTemplateInstanceMetadataOptions -> String
showsPrec :: Int -> LaunchTemplateInstanceMetadataOptions -> ShowS
$cshowsPrec :: Int -> LaunchTemplateInstanceMetadataOptions -> ShowS
Prelude.Show, forall x.
Rep LaunchTemplateInstanceMetadataOptions x
-> LaunchTemplateInstanceMetadataOptions
forall x.
LaunchTemplateInstanceMetadataOptions
-> Rep LaunchTemplateInstanceMetadataOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep LaunchTemplateInstanceMetadataOptions x
-> LaunchTemplateInstanceMetadataOptions
$cfrom :: forall x.
LaunchTemplateInstanceMetadataOptions
-> Rep LaunchTemplateInstanceMetadataOptions x
Prelude.Generic)

-- |
-- Create a value of 'LaunchTemplateInstanceMetadataOptions' 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:
--
-- 'httpEndpoint', 'launchTemplateInstanceMetadataOptions_httpEndpoint' - Enables or disables the HTTP metadata endpoint on your instances. If the
-- parameter is not specified, the default state is @enabled@.
--
-- If you specify a value of @disabled@, you will not be able to access
-- your instance metadata.
--
-- 'httpProtocolIpv6', 'launchTemplateInstanceMetadataOptions_httpProtocolIpv6' - Enables or disables the IPv6 endpoint for the instance metadata service.
--
-- Default: @disabled@
--
-- 'httpPutResponseHopLimit', 'launchTemplateInstanceMetadataOptions_httpPutResponseHopLimit' - The desired HTTP PUT response hop limit for instance metadata requests.
-- The larger the number, the further instance metadata requests can
-- travel.
--
-- Default: 1
--
-- Possible values: Integers from 1 to 64
--
-- 'httpTokens', 'launchTemplateInstanceMetadataOptions_httpTokens' - The state of token usage for your instance metadata requests. If the
-- parameter is not specified in the request, the default state is
-- @optional@.
--
-- If the state is @optional@, you can choose to retrieve instance metadata
-- with or without a signed token header on your request. If you retrieve
-- the IAM role credentials without a token, the version 1.0 role
-- credentials are returned. If you retrieve the IAM role credentials using
-- a valid signed token, the version 2.0 role credentials are returned.
--
-- If the state is @required@, you must send a signed token header with any
-- instance metadata retrieval requests. In this state, retrieving the IAM
-- role credentials always returns the version 2.0 credentials; the version
-- 1.0 credentials are not available.
--
-- 'instanceMetadataTags', 'launchTemplateInstanceMetadataOptions_instanceMetadataTags' - Set to @enabled@ to allow access to instance tags from the instance
-- metadata. Set to @disabled@ to turn off access to instance tags from the
-- instance metadata. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/Using_Tags.html#work-with-tags-in-IMDS Work with instance tags using the instance metadata>.
--
-- Default: @disabled@
--
-- 'state', 'launchTemplateInstanceMetadataOptions_state' - The state of the metadata option changes.
--
-- @pending@ - The metadata options are being updated and the instance is
-- not ready to process metadata traffic with the new selection.
--
-- @applied@ - The metadata options have been successfully applied on the
-- instance.
newLaunchTemplateInstanceMetadataOptions ::
  LaunchTemplateInstanceMetadataOptions
newLaunchTemplateInstanceMetadataOptions :: LaunchTemplateInstanceMetadataOptions
newLaunchTemplateInstanceMetadataOptions =
  LaunchTemplateInstanceMetadataOptions'
    { $sel:httpEndpoint:LaunchTemplateInstanceMetadataOptions' :: Maybe LaunchTemplateInstanceMetadataEndpointState
httpEndpoint =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpProtocolIpv6:LaunchTemplateInstanceMetadataOptions' :: Maybe LaunchTemplateInstanceMetadataProtocolIpv6
httpProtocolIpv6 = forall a. Maybe a
Prelude.Nothing,
      $sel:httpPutResponseHopLimit:LaunchTemplateInstanceMetadataOptions' :: Maybe Int
httpPutResponseHopLimit =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpTokens:LaunchTemplateInstanceMetadataOptions' :: Maybe LaunchTemplateHttpTokensState
httpTokens = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceMetadataTags:LaunchTemplateInstanceMetadataOptions' :: Maybe LaunchTemplateInstanceMetadataTagsState
instanceMetadataTags =
        forall a. Maybe a
Prelude.Nothing,
      $sel:state:LaunchTemplateInstanceMetadataOptions' :: Maybe LaunchTemplateInstanceMetadataOptionsState
state = forall a. Maybe a
Prelude.Nothing
    }

-- | Enables or disables the HTTP metadata endpoint on your instances. If the
-- parameter is not specified, the default state is @enabled@.
--
-- If you specify a value of @disabled@, you will not be able to access
-- your instance metadata.
launchTemplateInstanceMetadataOptions_httpEndpoint :: Lens.Lens' LaunchTemplateInstanceMetadataOptions (Prelude.Maybe LaunchTemplateInstanceMetadataEndpointState)
launchTemplateInstanceMetadataOptions_httpEndpoint :: Lens'
  LaunchTemplateInstanceMetadataOptions
  (Maybe LaunchTemplateInstanceMetadataEndpointState)
launchTemplateInstanceMetadataOptions_httpEndpoint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateInstanceMetadataOptions' {Maybe LaunchTemplateInstanceMetadataEndpointState
httpEndpoint :: Maybe LaunchTemplateInstanceMetadataEndpointState
$sel:httpEndpoint:LaunchTemplateInstanceMetadataOptions' :: LaunchTemplateInstanceMetadataOptions
-> Maybe LaunchTemplateInstanceMetadataEndpointState
httpEndpoint} -> Maybe LaunchTemplateInstanceMetadataEndpointState
httpEndpoint) (\s :: LaunchTemplateInstanceMetadataOptions
s@LaunchTemplateInstanceMetadataOptions' {} Maybe LaunchTemplateInstanceMetadataEndpointState
a -> LaunchTemplateInstanceMetadataOptions
s {$sel:httpEndpoint:LaunchTemplateInstanceMetadataOptions' :: Maybe LaunchTemplateInstanceMetadataEndpointState
httpEndpoint = Maybe LaunchTemplateInstanceMetadataEndpointState
a} :: LaunchTemplateInstanceMetadataOptions)

-- | Enables or disables the IPv6 endpoint for the instance metadata service.
--
-- Default: @disabled@
launchTemplateInstanceMetadataOptions_httpProtocolIpv6 :: Lens.Lens' LaunchTemplateInstanceMetadataOptions (Prelude.Maybe LaunchTemplateInstanceMetadataProtocolIpv6)
launchTemplateInstanceMetadataOptions_httpProtocolIpv6 :: Lens'
  LaunchTemplateInstanceMetadataOptions
  (Maybe LaunchTemplateInstanceMetadataProtocolIpv6)
launchTemplateInstanceMetadataOptions_httpProtocolIpv6 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateInstanceMetadataOptions' {Maybe LaunchTemplateInstanceMetadataProtocolIpv6
httpProtocolIpv6 :: Maybe LaunchTemplateInstanceMetadataProtocolIpv6
$sel:httpProtocolIpv6:LaunchTemplateInstanceMetadataOptions' :: LaunchTemplateInstanceMetadataOptions
-> Maybe LaunchTemplateInstanceMetadataProtocolIpv6
httpProtocolIpv6} -> Maybe LaunchTemplateInstanceMetadataProtocolIpv6
httpProtocolIpv6) (\s :: LaunchTemplateInstanceMetadataOptions
s@LaunchTemplateInstanceMetadataOptions' {} Maybe LaunchTemplateInstanceMetadataProtocolIpv6
a -> LaunchTemplateInstanceMetadataOptions
s {$sel:httpProtocolIpv6:LaunchTemplateInstanceMetadataOptions' :: Maybe LaunchTemplateInstanceMetadataProtocolIpv6
httpProtocolIpv6 = Maybe LaunchTemplateInstanceMetadataProtocolIpv6
a} :: LaunchTemplateInstanceMetadataOptions)

-- | The desired HTTP PUT response hop limit for instance metadata requests.
-- The larger the number, the further instance metadata requests can
-- travel.
--
-- Default: 1
--
-- Possible values: Integers from 1 to 64
launchTemplateInstanceMetadataOptions_httpPutResponseHopLimit :: Lens.Lens' LaunchTemplateInstanceMetadataOptions (Prelude.Maybe Prelude.Int)
launchTemplateInstanceMetadataOptions_httpPutResponseHopLimit :: Lens' LaunchTemplateInstanceMetadataOptions (Maybe Int)
launchTemplateInstanceMetadataOptions_httpPutResponseHopLimit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateInstanceMetadataOptions' {Maybe Int
httpPutResponseHopLimit :: Maybe Int
$sel:httpPutResponseHopLimit:LaunchTemplateInstanceMetadataOptions' :: LaunchTemplateInstanceMetadataOptions -> Maybe Int
httpPutResponseHopLimit} -> Maybe Int
httpPutResponseHopLimit) (\s :: LaunchTemplateInstanceMetadataOptions
s@LaunchTemplateInstanceMetadataOptions' {} Maybe Int
a -> LaunchTemplateInstanceMetadataOptions
s {$sel:httpPutResponseHopLimit:LaunchTemplateInstanceMetadataOptions' :: Maybe Int
httpPutResponseHopLimit = Maybe Int
a} :: LaunchTemplateInstanceMetadataOptions)

-- | The state of token usage for your instance metadata requests. If the
-- parameter is not specified in the request, the default state is
-- @optional@.
--
-- If the state is @optional@, you can choose to retrieve instance metadata
-- with or without a signed token header on your request. If you retrieve
-- the IAM role credentials without a token, the version 1.0 role
-- credentials are returned. If you retrieve the IAM role credentials using
-- a valid signed token, the version 2.0 role credentials are returned.
--
-- If the state is @required@, you must send a signed token header with any
-- instance metadata retrieval requests. In this state, retrieving the IAM
-- role credentials always returns the version 2.0 credentials; the version
-- 1.0 credentials are not available.
launchTemplateInstanceMetadataOptions_httpTokens :: Lens.Lens' LaunchTemplateInstanceMetadataOptions (Prelude.Maybe LaunchTemplateHttpTokensState)
launchTemplateInstanceMetadataOptions_httpTokens :: Lens'
  LaunchTemplateInstanceMetadataOptions
  (Maybe LaunchTemplateHttpTokensState)
launchTemplateInstanceMetadataOptions_httpTokens = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateInstanceMetadataOptions' {Maybe LaunchTemplateHttpTokensState
httpTokens :: Maybe LaunchTemplateHttpTokensState
$sel:httpTokens:LaunchTemplateInstanceMetadataOptions' :: LaunchTemplateInstanceMetadataOptions
-> Maybe LaunchTemplateHttpTokensState
httpTokens} -> Maybe LaunchTemplateHttpTokensState
httpTokens) (\s :: LaunchTemplateInstanceMetadataOptions
s@LaunchTemplateInstanceMetadataOptions' {} Maybe LaunchTemplateHttpTokensState
a -> LaunchTemplateInstanceMetadataOptions
s {$sel:httpTokens:LaunchTemplateInstanceMetadataOptions' :: Maybe LaunchTemplateHttpTokensState
httpTokens = Maybe LaunchTemplateHttpTokensState
a} :: LaunchTemplateInstanceMetadataOptions)

-- | Set to @enabled@ to allow access to instance tags from the instance
-- metadata. Set to @disabled@ to turn off access to instance tags from the
-- instance metadata. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/Using_Tags.html#work-with-tags-in-IMDS Work with instance tags using the instance metadata>.
--
-- Default: @disabled@
launchTemplateInstanceMetadataOptions_instanceMetadataTags :: Lens.Lens' LaunchTemplateInstanceMetadataOptions (Prelude.Maybe LaunchTemplateInstanceMetadataTagsState)
launchTemplateInstanceMetadataOptions_instanceMetadataTags :: Lens'
  LaunchTemplateInstanceMetadataOptions
  (Maybe LaunchTemplateInstanceMetadataTagsState)
launchTemplateInstanceMetadataOptions_instanceMetadataTags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateInstanceMetadataOptions' {Maybe LaunchTemplateInstanceMetadataTagsState
instanceMetadataTags :: Maybe LaunchTemplateInstanceMetadataTagsState
$sel:instanceMetadataTags:LaunchTemplateInstanceMetadataOptions' :: LaunchTemplateInstanceMetadataOptions
-> Maybe LaunchTemplateInstanceMetadataTagsState
instanceMetadataTags} -> Maybe LaunchTemplateInstanceMetadataTagsState
instanceMetadataTags) (\s :: LaunchTemplateInstanceMetadataOptions
s@LaunchTemplateInstanceMetadataOptions' {} Maybe LaunchTemplateInstanceMetadataTagsState
a -> LaunchTemplateInstanceMetadataOptions
s {$sel:instanceMetadataTags:LaunchTemplateInstanceMetadataOptions' :: Maybe LaunchTemplateInstanceMetadataTagsState
instanceMetadataTags = Maybe LaunchTemplateInstanceMetadataTagsState
a} :: LaunchTemplateInstanceMetadataOptions)

-- | The state of the metadata option changes.
--
-- @pending@ - The metadata options are being updated and the instance is
-- not ready to process metadata traffic with the new selection.
--
-- @applied@ - The metadata options have been successfully applied on the
-- instance.
launchTemplateInstanceMetadataOptions_state :: Lens.Lens' LaunchTemplateInstanceMetadataOptions (Prelude.Maybe LaunchTemplateInstanceMetadataOptionsState)
launchTemplateInstanceMetadataOptions_state :: Lens'
  LaunchTemplateInstanceMetadataOptions
  (Maybe LaunchTemplateInstanceMetadataOptionsState)
launchTemplateInstanceMetadataOptions_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplateInstanceMetadataOptions' {Maybe LaunchTemplateInstanceMetadataOptionsState
state :: Maybe LaunchTemplateInstanceMetadataOptionsState
$sel:state:LaunchTemplateInstanceMetadataOptions' :: LaunchTemplateInstanceMetadataOptions
-> Maybe LaunchTemplateInstanceMetadataOptionsState
state} -> Maybe LaunchTemplateInstanceMetadataOptionsState
state) (\s :: LaunchTemplateInstanceMetadataOptions
s@LaunchTemplateInstanceMetadataOptions' {} Maybe LaunchTemplateInstanceMetadataOptionsState
a -> LaunchTemplateInstanceMetadataOptions
s {$sel:state:LaunchTemplateInstanceMetadataOptions' :: Maybe LaunchTemplateInstanceMetadataOptionsState
state = Maybe LaunchTemplateInstanceMetadataOptionsState
a} :: LaunchTemplateInstanceMetadataOptions)

instance
  Data.FromXML
    LaunchTemplateInstanceMetadataOptions
  where
  parseXML :: [Node] -> Either String LaunchTemplateInstanceMetadataOptions
parseXML [Node]
x =
    Maybe LaunchTemplateInstanceMetadataEndpointState
-> Maybe LaunchTemplateInstanceMetadataProtocolIpv6
-> Maybe Int
-> Maybe LaunchTemplateHttpTokensState
-> Maybe LaunchTemplateInstanceMetadataTagsState
-> Maybe LaunchTemplateInstanceMetadataOptionsState
-> LaunchTemplateInstanceMetadataOptions
LaunchTemplateInstanceMetadataOptions'
      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
"httpEndpoint")
      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
"httpProtocolIpv6")
      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
"httpPutResponseHopLimit")
      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
"httpTokens")
      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
"instanceMetadataTags")
      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
"state")

instance
  Prelude.Hashable
    LaunchTemplateInstanceMetadataOptions
  where
  hashWithSalt :: Int -> LaunchTemplateInstanceMetadataOptions -> Int
hashWithSalt
    Int
_salt
    LaunchTemplateInstanceMetadataOptions' {Maybe Int
Maybe LaunchTemplateHttpTokensState
Maybe LaunchTemplateInstanceMetadataEndpointState
Maybe LaunchTemplateInstanceMetadataOptionsState
Maybe LaunchTemplateInstanceMetadataProtocolIpv6
Maybe LaunchTemplateInstanceMetadataTagsState
state :: Maybe LaunchTemplateInstanceMetadataOptionsState
instanceMetadataTags :: Maybe LaunchTemplateInstanceMetadataTagsState
httpTokens :: Maybe LaunchTemplateHttpTokensState
httpPutResponseHopLimit :: Maybe Int
httpProtocolIpv6 :: Maybe LaunchTemplateInstanceMetadataProtocolIpv6
httpEndpoint :: Maybe LaunchTemplateInstanceMetadataEndpointState
$sel:state:LaunchTemplateInstanceMetadataOptions' :: LaunchTemplateInstanceMetadataOptions
-> Maybe LaunchTemplateInstanceMetadataOptionsState
$sel:instanceMetadataTags:LaunchTemplateInstanceMetadataOptions' :: LaunchTemplateInstanceMetadataOptions
-> Maybe LaunchTemplateInstanceMetadataTagsState
$sel:httpTokens:LaunchTemplateInstanceMetadataOptions' :: LaunchTemplateInstanceMetadataOptions
-> Maybe LaunchTemplateHttpTokensState
$sel:httpPutResponseHopLimit:LaunchTemplateInstanceMetadataOptions' :: LaunchTemplateInstanceMetadataOptions -> Maybe Int
$sel:httpProtocolIpv6:LaunchTemplateInstanceMetadataOptions' :: LaunchTemplateInstanceMetadataOptions
-> Maybe LaunchTemplateInstanceMetadataProtocolIpv6
$sel:httpEndpoint:LaunchTemplateInstanceMetadataOptions' :: LaunchTemplateInstanceMetadataOptions
-> Maybe LaunchTemplateInstanceMetadataEndpointState
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LaunchTemplateInstanceMetadataEndpointState
httpEndpoint
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LaunchTemplateInstanceMetadataProtocolIpv6
httpProtocolIpv6
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
httpPutResponseHopLimit
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LaunchTemplateHttpTokensState
httpTokens
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LaunchTemplateInstanceMetadataTagsState
instanceMetadataTags
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LaunchTemplateInstanceMetadataOptionsState
state

instance
  Prelude.NFData
    LaunchTemplateInstanceMetadataOptions
  where
  rnf :: LaunchTemplateInstanceMetadataOptions -> ()
rnf LaunchTemplateInstanceMetadataOptions' {Maybe Int
Maybe LaunchTemplateHttpTokensState
Maybe LaunchTemplateInstanceMetadataEndpointState
Maybe LaunchTemplateInstanceMetadataOptionsState
Maybe LaunchTemplateInstanceMetadataProtocolIpv6
Maybe LaunchTemplateInstanceMetadataTagsState
state :: Maybe LaunchTemplateInstanceMetadataOptionsState
instanceMetadataTags :: Maybe LaunchTemplateInstanceMetadataTagsState
httpTokens :: Maybe LaunchTemplateHttpTokensState
httpPutResponseHopLimit :: Maybe Int
httpProtocolIpv6 :: Maybe LaunchTemplateInstanceMetadataProtocolIpv6
httpEndpoint :: Maybe LaunchTemplateInstanceMetadataEndpointState
$sel:state:LaunchTemplateInstanceMetadataOptions' :: LaunchTemplateInstanceMetadataOptions
-> Maybe LaunchTemplateInstanceMetadataOptionsState
$sel:instanceMetadataTags:LaunchTemplateInstanceMetadataOptions' :: LaunchTemplateInstanceMetadataOptions
-> Maybe LaunchTemplateInstanceMetadataTagsState
$sel:httpTokens:LaunchTemplateInstanceMetadataOptions' :: LaunchTemplateInstanceMetadataOptions
-> Maybe LaunchTemplateHttpTokensState
$sel:httpPutResponseHopLimit:LaunchTemplateInstanceMetadataOptions' :: LaunchTemplateInstanceMetadataOptions -> Maybe Int
$sel:httpProtocolIpv6:LaunchTemplateInstanceMetadataOptions' :: LaunchTemplateInstanceMetadataOptions
-> Maybe LaunchTemplateInstanceMetadataProtocolIpv6
$sel:httpEndpoint:LaunchTemplateInstanceMetadataOptions' :: LaunchTemplateInstanceMetadataOptions
-> Maybe LaunchTemplateInstanceMetadataEndpointState
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe LaunchTemplateInstanceMetadataEndpointState
httpEndpoint
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LaunchTemplateInstanceMetadataProtocolIpv6
httpProtocolIpv6
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
httpPutResponseHopLimit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LaunchTemplateHttpTokensState
httpTokens
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LaunchTemplateInstanceMetadataTagsState
instanceMetadataTags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LaunchTemplateInstanceMetadataOptionsState
state