{-# 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.AutoScaling.Types.AutoScalingInstanceDetails
-- 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.AutoScaling.Types.AutoScalingInstanceDetails where

import Amazonka.AutoScaling.Types.LaunchTemplateSpecification
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | Describes an EC2 instance associated with an Auto Scaling group.
--
-- /See:/ 'newAutoScalingInstanceDetails' smart constructor.
data AutoScalingInstanceDetails = AutoScalingInstanceDetails'
  { -- | The instance type of the EC2 instance.
    AutoScalingInstanceDetails -> Maybe Text
instanceType :: Prelude.Maybe Prelude.Text,
    -- | The launch configuration used to launch the instance. This value is not
    -- available if you attached the instance to the Auto Scaling group.
    AutoScalingInstanceDetails -> Maybe Text
launchConfigurationName :: Prelude.Maybe Prelude.Text,
    -- | The launch template for the instance.
    AutoScalingInstanceDetails -> Maybe LaunchTemplateSpecification
launchTemplate :: Prelude.Maybe LaunchTemplateSpecification,
    -- | The number of capacity units contributed by the instance based on its
    -- instance type.
    --
    -- Valid Range: Minimum value of 1. Maximum value of 999.
    AutoScalingInstanceDetails -> Maybe Text
weightedCapacity :: Prelude.Maybe Prelude.Text,
    -- | The ID of the instance.
    AutoScalingInstanceDetails -> Text
instanceId :: Prelude.Text,
    -- | The name of the Auto Scaling group for the instance.
    AutoScalingInstanceDetails -> Text
autoScalingGroupName :: Prelude.Text,
    -- | The Availability Zone for the instance.
    AutoScalingInstanceDetails -> Text
availabilityZone :: Prelude.Text,
    -- | The lifecycle state for the instance. The @Quarantined@ state is not
    -- used. For information about lifecycle states, see
    -- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/AutoScalingGroupLifecycle.html Instance lifecycle>
    -- in the /Amazon EC2 Auto Scaling User Guide/.
    --
    -- Valid values: @Pending@ | @Pending:Wait@ | @Pending:Proceed@ |
    -- @Quarantined@ | @InService@ | @Terminating@ | @Terminating:Wait@ |
    -- @Terminating:Proceed@ | @Terminated@ | @Detaching@ | @Detached@ |
    -- @EnteringStandby@ | @Standby@ | @Warmed:Pending@ | @Warmed:Pending:Wait@
    -- | @Warmed:Pending:Proceed@ | @Warmed:Terminating@ |
    -- @Warmed:Terminating:Wait@ | @Warmed:Terminating:Proceed@ |
    -- @Warmed:Terminated@ | @Warmed:Stopped@ | @Warmed:Running@
    AutoScalingInstanceDetails -> Text
lifecycleState :: Prelude.Text,
    -- | The last reported health status of this instance. \"Healthy\" means that
    -- the instance is healthy and should remain in service. \"Unhealthy\"
    -- means that the instance is unhealthy and Amazon EC2 Auto Scaling should
    -- terminate and replace it.
    AutoScalingInstanceDetails -> Text
healthStatus :: Prelude.Text,
    -- | Indicates whether the instance is protected from termination by Amazon
    -- EC2 Auto Scaling when scaling in.
    AutoScalingInstanceDetails -> Bool
protectedFromScaleIn :: Prelude.Bool
  }
  deriving (AutoScalingInstanceDetails -> AutoScalingInstanceDetails -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AutoScalingInstanceDetails -> AutoScalingInstanceDetails -> Bool
$c/= :: AutoScalingInstanceDetails -> AutoScalingInstanceDetails -> Bool
== :: AutoScalingInstanceDetails -> AutoScalingInstanceDetails -> Bool
$c== :: AutoScalingInstanceDetails -> AutoScalingInstanceDetails -> Bool
Prelude.Eq, ReadPrec [AutoScalingInstanceDetails]
ReadPrec AutoScalingInstanceDetails
Int -> ReadS AutoScalingInstanceDetails
ReadS [AutoScalingInstanceDetails]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AutoScalingInstanceDetails]
$creadListPrec :: ReadPrec [AutoScalingInstanceDetails]
readPrec :: ReadPrec AutoScalingInstanceDetails
$creadPrec :: ReadPrec AutoScalingInstanceDetails
readList :: ReadS [AutoScalingInstanceDetails]
$creadList :: ReadS [AutoScalingInstanceDetails]
readsPrec :: Int -> ReadS AutoScalingInstanceDetails
$creadsPrec :: Int -> ReadS AutoScalingInstanceDetails
Prelude.Read, Int -> AutoScalingInstanceDetails -> ShowS
[AutoScalingInstanceDetails] -> ShowS
AutoScalingInstanceDetails -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AutoScalingInstanceDetails] -> ShowS
$cshowList :: [AutoScalingInstanceDetails] -> ShowS
show :: AutoScalingInstanceDetails -> String
$cshow :: AutoScalingInstanceDetails -> String
showsPrec :: Int -> AutoScalingInstanceDetails -> ShowS
$cshowsPrec :: Int -> AutoScalingInstanceDetails -> ShowS
Prelude.Show, forall x.
Rep AutoScalingInstanceDetails x -> AutoScalingInstanceDetails
forall x.
AutoScalingInstanceDetails -> Rep AutoScalingInstanceDetails x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AutoScalingInstanceDetails x -> AutoScalingInstanceDetails
$cfrom :: forall x.
AutoScalingInstanceDetails -> Rep AutoScalingInstanceDetails x
Prelude.Generic)

-- |
-- Create a value of 'AutoScalingInstanceDetails' 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:
--
-- 'instanceType', 'autoScalingInstanceDetails_instanceType' - The instance type of the EC2 instance.
--
-- 'launchConfigurationName', 'autoScalingInstanceDetails_launchConfigurationName' - The launch configuration used to launch the instance. This value is not
-- available if you attached the instance to the Auto Scaling group.
--
-- 'launchTemplate', 'autoScalingInstanceDetails_launchTemplate' - The launch template for the instance.
--
-- 'weightedCapacity', 'autoScalingInstanceDetails_weightedCapacity' - The number of capacity units contributed by the instance based on its
-- instance type.
--
-- Valid Range: Minimum value of 1. Maximum value of 999.
--
-- 'instanceId', 'autoScalingInstanceDetails_instanceId' - The ID of the instance.
--
-- 'autoScalingGroupName', 'autoScalingInstanceDetails_autoScalingGroupName' - The name of the Auto Scaling group for the instance.
--
-- 'availabilityZone', 'autoScalingInstanceDetails_availabilityZone' - The Availability Zone for the instance.
--
-- 'lifecycleState', 'autoScalingInstanceDetails_lifecycleState' - The lifecycle state for the instance. The @Quarantined@ state is not
-- used. For information about lifecycle states, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/AutoScalingGroupLifecycle.html Instance lifecycle>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- Valid values: @Pending@ | @Pending:Wait@ | @Pending:Proceed@ |
-- @Quarantined@ | @InService@ | @Terminating@ | @Terminating:Wait@ |
-- @Terminating:Proceed@ | @Terminated@ | @Detaching@ | @Detached@ |
-- @EnteringStandby@ | @Standby@ | @Warmed:Pending@ | @Warmed:Pending:Wait@
-- | @Warmed:Pending:Proceed@ | @Warmed:Terminating@ |
-- @Warmed:Terminating:Wait@ | @Warmed:Terminating:Proceed@ |
-- @Warmed:Terminated@ | @Warmed:Stopped@ | @Warmed:Running@
--
-- 'healthStatus', 'autoScalingInstanceDetails_healthStatus' - The last reported health status of this instance. \"Healthy\" means that
-- the instance is healthy and should remain in service. \"Unhealthy\"
-- means that the instance is unhealthy and Amazon EC2 Auto Scaling should
-- terminate and replace it.
--
-- 'protectedFromScaleIn', 'autoScalingInstanceDetails_protectedFromScaleIn' - Indicates whether the instance is protected from termination by Amazon
-- EC2 Auto Scaling when scaling in.
newAutoScalingInstanceDetails ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'autoScalingGroupName'
  Prelude.Text ->
  -- | 'availabilityZone'
  Prelude.Text ->
  -- | 'lifecycleState'
  Prelude.Text ->
  -- | 'healthStatus'
  Prelude.Text ->
  -- | 'protectedFromScaleIn'
  Prelude.Bool ->
  AutoScalingInstanceDetails
newAutoScalingInstanceDetails :: Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> AutoScalingInstanceDetails
newAutoScalingInstanceDetails
  Text
pInstanceId_
  Text
pAutoScalingGroupName_
  Text
pAvailabilityZone_
  Text
pLifecycleState_
  Text
pHealthStatus_
  Bool
pProtectedFromScaleIn_ =
    AutoScalingInstanceDetails'
      { $sel:instanceType:AutoScalingInstanceDetails' :: Maybe Text
instanceType =
          forall a. Maybe a
Prelude.Nothing,
        $sel:launchConfigurationName:AutoScalingInstanceDetails' :: Maybe Text
launchConfigurationName = forall a. Maybe a
Prelude.Nothing,
        $sel:launchTemplate:AutoScalingInstanceDetails' :: Maybe LaunchTemplateSpecification
launchTemplate = forall a. Maybe a
Prelude.Nothing,
        $sel:weightedCapacity:AutoScalingInstanceDetails' :: Maybe Text
weightedCapacity = forall a. Maybe a
Prelude.Nothing,
        $sel:instanceId:AutoScalingInstanceDetails' :: Text
instanceId = Text
pInstanceId_,
        $sel:autoScalingGroupName:AutoScalingInstanceDetails' :: Text
autoScalingGroupName = Text
pAutoScalingGroupName_,
        $sel:availabilityZone:AutoScalingInstanceDetails' :: Text
availabilityZone = Text
pAvailabilityZone_,
        $sel:lifecycleState:AutoScalingInstanceDetails' :: Text
lifecycleState = Text
pLifecycleState_,
        $sel:healthStatus:AutoScalingInstanceDetails' :: Text
healthStatus = Text
pHealthStatus_,
        $sel:protectedFromScaleIn:AutoScalingInstanceDetails' :: Bool
protectedFromScaleIn = Bool
pProtectedFromScaleIn_
      }

-- | The instance type of the EC2 instance.
autoScalingInstanceDetails_instanceType :: Lens.Lens' AutoScalingInstanceDetails (Prelude.Maybe Prelude.Text)
autoScalingInstanceDetails_instanceType :: Lens' AutoScalingInstanceDetails (Maybe Text)
autoScalingInstanceDetails_instanceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingInstanceDetails' {Maybe Text
instanceType :: Maybe Text
$sel:instanceType:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Maybe Text
instanceType} -> Maybe Text
instanceType) (\s :: AutoScalingInstanceDetails
s@AutoScalingInstanceDetails' {} Maybe Text
a -> AutoScalingInstanceDetails
s {$sel:instanceType:AutoScalingInstanceDetails' :: Maybe Text
instanceType = Maybe Text
a} :: AutoScalingInstanceDetails)

-- | The launch configuration used to launch the instance. This value is not
-- available if you attached the instance to the Auto Scaling group.
autoScalingInstanceDetails_launchConfigurationName :: Lens.Lens' AutoScalingInstanceDetails (Prelude.Maybe Prelude.Text)
autoScalingInstanceDetails_launchConfigurationName :: Lens' AutoScalingInstanceDetails (Maybe Text)
autoScalingInstanceDetails_launchConfigurationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingInstanceDetails' {Maybe Text
launchConfigurationName :: Maybe Text
$sel:launchConfigurationName:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Maybe Text
launchConfigurationName} -> Maybe Text
launchConfigurationName) (\s :: AutoScalingInstanceDetails
s@AutoScalingInstanceDetails' {} Maybe Text
a -> AutoScalingInstanceDetails
s {$sel:launchConfigurationName:AutoScalingInstanceDetails' :: Maybe Text
launchConfigurationName = Maybe Text
a} :: AutoScalingInstanceDetails)

-- | The launch template for the instance.
autoScalingInstanceDetails_launchTemplate :: Lens.Lens' AutoScalingInstanceDetails (Prelude.Maybe LaunchTemplateSpecification)
autoScalingInstanceDetails_launchTemplate :: Lens'
  AutoScalingInstanceDetails (Maybe LaunchTemplateSpecification)
autoScalingInstanceDetails_launchTemplate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingInstanceDetails' {Maybe LaunchTemplateSpecification
launchTemplate :: Maybe LaunchTemplateSpecification
$sel:launchTemplate:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Maybe LaunchTemplateSpecification
launchTemplate} -> Maybe LaunchTemplateSpecification
launchTemplate) (\s :: AutoScalingInstanceDetails
s@AutoScalingInstanceDetails' {} Maybe LaunchTemplateSpecification
a -> AutoScalingInstanceDetails
s {$sel:launchTemplate:AutoScalingInstanceDetails' :: Maybe LaunchTemplateSpecification
launchTemplate = Maybe LaunchTemplateSpecification
a} :: AutoScalingInstanceDetails)

-- | The number of capacity units contributed by the instance based on its
-- instance type.
--
-- Valid Range: Minimum value of 1. Maximum value of 999.
autoScalingInstanceDetails_weightedCapacity :: Lens.Lens' AutoScalingInstanceDetails (Prelude.Maybe Prelude.Text)
autoScalingInstanceDetails_weightedCapacity :: Lens' AutoScalingInstanceDetails (Maybe Text)
autoScalingInstanceDetails_weightedCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingInstanceDetails' {Maybe Text
weightedCapacity :: Maybe Text
$sel:weightedCapacity:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Maybe Text
weightedCapacity} -> Maybe Text
weightedCapacity) (\s :: AutoScalingInstanceDetails
s@AutoScalingInstanceDetails' {} Maybe Text
a -> AutoScalingInstanceDetails
s {$sel:weightedCapacity:AutoScalingInstanceDetails' :: Maybe Text
weightedCapacity = Maybe Text
a} :: AutoScalingInstanceDetails)

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

-- | The name of the Auto Scaling group for the instance.
autoScalingInstanceDetails_autoScalingGroupName :: Lens.Lens' AutoScalingInstanceDetails Prelude.Text
autoScalingInstanceDetails_autoScalingGroupName :: Lens' AutoScalingInstanceDetails Text
autoScalingInstanceDetails_autoScalingGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingInstanceDetails' {Text
autoScalingGroupName :: Text
$sel:autoScalingGroupName:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Text
autoScalingGroupName} -> Text
autoScalingGroupName) (\s :: AutoScalingInstanceDetails
s@AutoScalingInstanceDetails' {} Text
a -> AutoScalingInstanceDetails
s {$sel:autoScalingGroupName:AutoScalingInstanceDetails' :: Text
autoScalingGroupName = Text
a} :: AutoScalingInstanceDetails)

-- | The Availability Zone for the instance.
autoScalingInstanceDetails_availabilityZone :: Lens.Lens' AutoScalingInstanceDetails Prelude.Text
autoScalingInstanceDetails_availabilityZone :: Lens' AutoScalingInstanceDetails Text
autoScalingInstanceDetails_availabilityZone = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingInstanceDetails' {Text
availabilityZone :: Text
$sel:availabilityZone:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Text
availabilityZone} -> Text
availabilityZone) (\s :: AutoScalingInstanceDetails
s@AutoScalingInstanceDetails' {} Text
a -> AutoScalingInstanceDetails
s {$sel:availabilityZone:AutoScalingInstanceDetails' :: Text
availabilityZone = Text
a} :: AutoScalingInstanceDetails)

-- | The lifecycle state for the instance. The @Quarantined@ state is not
-- used. For information about lifecycle states, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/AutoScalingGroupLifecycle.html Instance lifecycle>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- Valid values: @Pending@ | @Pending:Wait@ | @Pending:Proceed@ |
-- @Quarantined@ | @InService@ | @Terminating@ | @Terminating:Wait@ |
-- @Terminating:Proceed@ | @Terminated@ | @Detaching@ | @Detached@ |
-- @EnteringStandby@ | @Standby@ | @Warmed:Pending@ | @Warmed:Pending:Wait@
-- | @Warmed:Pending:Proceed@ | @Warmed:Terminating@ |
-- @Warmed:Terminating:Wait@ | @Warmed:Terminating:Proceed@ |
-- @Warmed:Terminated@ | @Warmed:Stopped@ | @Warmed:Running@
autoScalingInstanceDetails_lifecycleState :: Lens.Lens' AutoScalingInstanceDetails Prelude.Text
autoScalingInstanceDetails_lifecycleState :: Lens' AutoScalingInstanceDetails Text
autoScalingInstanceDetails_lifecycleState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingInstanceDetails' {Text
lifecycleState :: Text
$sel:lifecycleState:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Text
lifecycleState} -> Text
lifecycleState) (\s :: AutoScalingInstanceDetails
s@AutoScalingInstanceDetails' {} Text
a -> AutoScalingInstanceDetails
s {$sel:lifecycleState:AutoScalingInstanceDetails' :: Text
lifecycleState = Text
a} :: AutoScalingInstanceDetails)

-- | The last reported health status of this instance. \"Healthy\" means that
-- the instance is healthy and should remain in service. \"Unhealthy\"
-- means that the instance is unhealthy and Amazon EC2 Auto Scaling should
-- terminate and replace it.
autoScalingInstanceDetails_healthStatus :: Lens.Lens' AutoScalingInstanceDetails Prelude.Text
autoScalingInstanceDetails_healthStatus :: Lens' AutoScalingInstanceDetails Text
autoScalingInstanceDetails_healthStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingInstanceDetails' {Text
healthStatus :: Text
$sel:healthStatus:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Text
healthStatus} -> Text
healthStatus) (\s :: AutoScalingInstanceDetails
s@AutoScalingInstanceDetails' {} Text
a -> AutoScalingInstanceDetails
s {$sel:healthStatus:AutoScalingInstanceDetails' :: Text
healthStatus = Text
a} :: AutoScalingInstanceDetails)

-- | Indicates whether the instance is protected from termination by Amazon
-- EC2 Auto Scaling when scaling in.
autoScalingInstanceDetails_protectedFromScaleIn :: Lens.Lens' AutoScalingInstanceDetails Prelude.Bool
autoScalingInstanceDetails_protectedFromScaleIn :: Lens' AutoScalingInstanceDetails Bool
autoScalingInstanceDetails_protectedFromScaleIn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingInstanceDetails' {Bool
protectedFromScaleIn :: Bool
$sel:protectedFromScaleIn:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Bool
protectedFromScaleIn} -> Bool
protectedFromScaleIn) (\s :: AutoScalingInstanceDetails
s@AutoScalingInstanceDetails' {} Bool
a -> AutoScalingInstanceDetails
s {$sel:protectedFromScaleIn:AutoScalingInstanceDetails' :: Bool
protectedFromScaleIn = Bool
a} :: AutoScalingInstanceDetails)

instance Data.FromXML AutoScalingInstanceDetails where
  parseXML :: [Node] -> Either String AutoScalingInstanceDetails
parseXML [Node]
x =
    Maybe Text
-> Maybe Text
-> Maybe LaunchTemplateSpecification
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> AutoScalingInstanceDetails
AutoScalingInstanceDetails'
      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
"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
"LaunchConfigurationName")
      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
"LaunchTemplate")
      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
"WeightedCapacity")
      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
"AutoScalingGroupName")
      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
"AvailabilityZone")
      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
"LifecycleState")
      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
"HealthStatus")
      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
"ProtectedFromScaleIn")

instance Prelude.Hashable AutoScalingInstanceDetails where
  hashWithSalt :: Int -> AutoScalingInstanceDetails -> Int
hashWithSalt Int
_salt AutoScalingInstanceDetails' {Bool
Maybe Text
Maybe LaunchTemplateSpecification
Text
protectedFromScaleIn :: Bool
healthStatus :: Text
lifecycleState :: Text
availabilityZone :: Text
autoScalingGroupName :: Text
instanceId :: Text
weightedCapacity :: Maybe Text
launchTemplate :: Maybe LaunchTemplateSpecification
launchConfigurationName :: Maybe Text
instanceType :: Maybe Text
$sel:protectedFromScaleIn:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Bool
$sel:healthStatus:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Text
$sel:lifecycleState:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Text
$sel:availabilityZone:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Text
$sel:autoScalingGroupName:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Text
$sel:instanceId:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Text
$sel:weightedCapacity:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Maybe Text
$sel:launchTemplate:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Maybe LaunchTemplateSpecification
$sel:launchConfigurationName:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Maybe Text
$sel:instanceType:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
instanceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
launchConfigurationName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LaunchTemplateSpecification
launchTemplate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
weightedCapacity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
autoScalingGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
availabilityZone
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
lifecycleState
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
healthStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Bool
protectedFromScaleIn

instance Prelude.NFData AutoScalingInstanceDetails where
  rnf :: AutoScalingInstanceDetails -> ()
rnf AutoScalingInstanceDetails' {Bool
Maybe Text
Maybe LaunchTemplateSpecification
Text
protectedFromScaleIn :: Bool
healthStatus :: Text
lifecycleState :: Text
availabilityZone :: Text
autoScalingGroupName :: Text
instanceId :: Text
weightedCapacity :: Maybe Text
launchTemplate :: Maybe LaunchTemplateSpecification
launchConfigurationName :: Maybe Text
instanceType :: Maybe Text
$sel:protectedFromScaleIn:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Bool
$sel:healthStatus:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Text
$sel:lifecycleState:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Text
$sel:availabilityZone:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Text
$sel:autoScalingGroupName:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Text
$sel:instanceId:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Text
$sel:weightedCapacity:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Maybe Text
$sel:launchTemplate:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Maybe LaunchTemplateSpecification
$sel:launchConfigurationName:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Maybe Text
$sel:instanceType:AutoScalingInstanceDetails' :: AutoScalingInstanceDetails -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
instanceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
launchConfigurationName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LaunchTemplateSpecification
launchTemplate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
weightedCapacity
      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
autoScalingGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
availabilityZone
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
lifecycleState
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
healthStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Bool
protectedFromScaleIn