{-# 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.LaunchTemplatePlacement
-- 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.LaunchTemplatePlacement 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.Tenancy
import qualified Amazonka.Prelude as Prelude

-- | Describes the placement of an instance.
--
-- /See:/ 'newLaunchTemplatePlacement' smart constructor.
data LaunchTemplatePlacement = LaunchTemplatePlacement'
  { -- | The affinity setting for the instance on the Dedicated Host.
    LaunchTemplatePlacement -> Maybe Text
affinity :: Prelude.Maybe Prelude.Text,
    -- | The Availability Zone of the instance.
    LaunchTemplatePlacement -> Maybe Text
availabilityZone :: Prelude.Maybe Prelude.Text,
    -- | The Group ID of the placement group. You must specify the Placement
    -- Group __Group ID__ to launch an instance in a shared placement group.
    LaunchTemplatePlacement -> Maybe Text
groupId :: Prelude.Maybe Prelude.Text,
    -- | The name of the placement group for the instance.
    LaunchTemplatePlacement -> Maybe Text
groupName :: Prelude.Maybe Prelude.Text,
    -- | The ID of the Dedicated Host for the instance.
    LaunchTemplatePlacement -> Maybe Text
hostId :: Prelude.Maybe Prelude.Text,
    -- | The ARN of the host resource group in which to launch the instances.
    LaunchTemplatePlacement -> Maybe Text
hostResourceGroupArn :: Prelude.Maybe Prelude.Text,
    -- | The number of the partition the instance should launch in. Valid only if
    -- the placement group strategy is set to @partition@.
    LaunchTemplatePlacement -> Maybe Int
partitionNumber :: Prelude.Maybe Prelude.Int,
    -- | Reserved for future use.
    LaunchTemplatePlacement -> Maybe Text
spreadDomain :: Prelude.Maybe Prelude.Text,
    -- | The tenancy of the instance (if the instance is running in a VPC). An
    -- instance with a tenancy of @dedicated@ runs on single-tenant hardware.
    LaunchTemplatePlacement -> Maybe Tenancy
tenancy :: Prelude.Maybe Tenancy
  }
  deriving (LaunchTemplatePlacement -> LaunchTemplatePlacement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LaunchTemplatePlacement -> LaunchTemplatePlacement -> Bool
$c/= :: LaunchTemplatePlacement -> LaunchTemplatePlacement -> Bool
== :: LaunchTemplatePlacement -> LaunchTemplatePlacement -> Bool
$c== :: LaunchTemplatePlacement -> LaunchTemplatePlacement -> Bool
Prelude.Eq, ReadPrec [LaunchTemplatePlacement]
ReadPrec LaunchTemplatePlacement
Int -> ReadS LaunchTemplatePlacement
ReadS [LaunchTemplatePlacement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LaunchTemplatePlacement]
$creadListPrec :: ReadPrec [LaunchTemplatePlacement]
readPrec :: ReadPrec LaunchTemplatePlacement
$creadPrec :: ReadPrec LaunchTemplatePlacement
readList :: ReadS [LaunchTemplatePlacement]
$creadList :: ReadS [LaunchTemplatePlacement]
readsPrec :: Int -> ReadS LaunchTemplatePlacement
$creadsPrec :: Int -> ReadS LaunchTemplatePlacement
Prelude.Read, Int -> LaunchTemplatePlacement -> ShowS
[LaunchTemplatePlacement] -> ShowS
LaunchTemplatePlacement -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LaunchTemplatePlacement] -> ShowS
$cshowList :: [LaunchTemplatePlacement] -> ShowS
show :: LaunchTemplatePlacement -> String
$cshow :: LaunchTemplatePlacement -> String
showsPrec :: Int -> LaunchTemplatePlacement -> ShowS
$cshowsPrec :: Int -> LaunchTemplatePlacement -> ShowS
Prelude.Show, forall x. Rep LaunchTemplatePlacement x -> LaunchTemplatePlacement
forall x. LaunchTemplatePlacement -> Rep LaunchTemplatePlacement x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LaunchTemplatePlacement x -> LaunchTemplatePlacement
$cfrom :: forall x. LaunchTemplatePlacement -> Rep LaunchTemplatePlacement x
Prelude.Generic)

-- |
-- Create a value of 'LaunchTemplatePlacement' 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:
--
-- 'affinity', 'launchTemplatePlacement_affinity' - The affinity setting for the instance on the Dedicated Host.
--
-- 'availabilityZone', 'launchTemplatePlacement_availabilityZone' - The Availability Zone of the instance.
--
-- 'groupId', 'launchTemplatePlacement_groupId' - The Group ID of the placement group. You must specify the Placement
-- Group __Group ID__ to launch an instance in a shared placement group.
--
-- 'groupName', 'launchTemplatePlacement_groupName' - The name of the placement group for the instance.
--
-- 'hostId', 'launchTemplatePlacement_hostId' - The ID of the Dedicated Host for the instance.
--
-- 'hostResourceGroupArn', 'launchTemplatePlacement_hostResourceGroupArn' - The ARN of the host resource group in which to launch the instances.
--
-- 'partitionNumber', 'launchTemplatePlacement_partitionNumber' - The number of the partition the instance should launch in. Valid only if
-- the placement group strategy is set to @partition@.
--
-- 'spreadDomain', 'launchTemplatePlacement_spreadDomain' - Reserved for future use.
--
-- 'tenancy', 'launchTemplatePlacement_tenancy' - The tenancy of the instance (if the instance is running in a VPC). An
-- instance with a tenancy of @dedicated@ runs on single-tenant hardware.
newLaunchTemplatePlacement ::
  LaunchTemplatePlacement
newLaunchTemplatePlacement :: LaunchTemplatePlacement
newLaunchTemplatePlacement =
  LaunchTemplatePlacement'
    { $sel:affinity:LaunchTemplatePlacement' :: Maybe Text
affinity =
        forall a. Maybe a
Prelude.Nothing,
      $sel:availabilityZone:LaunchTemplatePlacement' :: Maybe Text
availabilityZone = forall a. Maybe a
Prelude.Nothing,
      $sel:groupId:LaunchTemplatePlacement' :: Maybe Text
groupId = forall a. Maybe a
Prelude.Nothing,
      $sel:groupName:LaunchTemplatePlacement' :: Maybe Text
groupName = forall a. Maybe a
Prelude.Nothing,
      $sel:hostId:LaunchTemplatePlacement' :: Maybe Text
hostId = forall a. Maybe a
Prelude.Nothing,
      $sel:hostResourceGroupArn:LaunchTemplatePlacement' :: Maybe Text
hostResourceGroupArn = forall a. Maybe a
Prelude.Nothing,
      $sel:partitionNumber:LaunchTemplatePlacement' :: Maybe Int
partitionNumber = forall a. Maybe a
Prelude.Nothing,
      $sel:spreadDomain:LaunchTemplatePlacement' :: Maybe Text
spreadDomain = forall a. Maybe a
Prelude.Nothing,
      $sel:tenancy:LaunchTemplatePlacement' :: Maybe Tenancy
tenancy = forall a. Maybe a
Prelude.Nothing
    }

-- | The affinity setting for the instance on the Dedicated Host.
launchTemplatePlacement_affinity :: Lens.Lens' LaunchTemplatePlacement (Prelude.Maybe Prelude.Text)
launchTemplatePlacement_affinity :: Lens' LaunchTemplatePlacement (Maybe Text)
launchTemplatePlacement_affinity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplatePlacement' {Maybe Text
affinity :: Maybe Text
$sel:affinity:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Text
affinity} -> Maybe Text
affinity) (\s :: LaunchTemplatePlacement
s@LaunchTemplatePlacement' {} Maybe Text
a -> LaunchTemplatePlacement
s {$sel:affinity:LaunchTemplatePlacement' :: Maybe Text
affinity = Maybe Text
a} :: LaunchTemplatePlacement)

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

-- | The Group ID of the placement group. You must specify the Placement
-- Group __Group ID__ to launch an instance in a shared placement group.
launchTemplatePlacement_groupId :: Lens.Lens' LaunchTemplatePlacement (Prelude.Maybe Prelude.Text)
launchTemplatePlacement_groupId :: Lens' LaunchTemplatePlacement (Maybe Text)
launchTemplatePlacement_groupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplatePlacement' {Maybe Text
groupId :: Maybe Text
$sel:groupId:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Text
groupId} -> Maybe Text
groupId) (\s :: LaunchTemplatePlacement
s@LaunchTemplatePlacement' {} Maybe Text
a -> LaunchTemplatePlacement
s {$sel:groupId:LaunchTemplatePlacement' :: Maybe Text
groupId = Maybe Text
a} :: LaunchTemplatePlacement)

-- | The name of the placement group for the instance.
launchTemplatePlacement_groupName :: Lens.Lens' LaunchTemplatePlacement (Prelude.Maybe Prelude.Text)
launchTemplatePlacement_groupName :: Lens' LaunchTemplatePlacement (Maybe Text)
launchTemplatePlacement_groupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplatePlacement' {Maybe Text
groupName :: Maybe Text
$sel:groupName:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Text
groupName} -> Maybe Text
groupName) (\s :: LaunchTemplatePlacement
s@LaunchTemplatePlacement' {} Maybe Text
a -> LaunchTemplatePlacement
s {$sel:groupName:LaunchTemplatePlacement' :: Maybe Text
groupName = Maybe Text
a} :: LaunchTemplatePlacement)

-- | The ID of the Dedicated Host for the instance.
launchTemplatePlacement_hostId :: Lens.Lens' LaunchTemplatePlacement (Prelude.Maybe Prelude.Text)
launchTemplatePlacement_hostId :: Lens' LaunchTemplatePlacement (Maybe Text)
launchTemplatePlacement_hostId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplatePlacement' {Maybe Text
hostId :: Maybe Text
$sel:hostId:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Text
hostId} -> Maybe Text
hostId) (\s :: LaunchTemplatePlacement
s@LaunchTemplatePlacement' {} Maybe Text
a -> LaunchTemplatePlacement
s {$sel:hostId:LaunchTemplatePlacement' :: Maybe Text
hostId = Maybe Text
a} :: LaunchTemplatePlacement)

-- | The ARN of the host resource group in which to launch the instances.
launchTemplatePlacement_hostResourceGroupArn :: Lens.Lens' LaunchTemplatePlacement (Prelude.Maybe Prelude.Text)
launchTemplatePlacement_hostResourceGroupArn :: Lens' LaunchTemplatePlacement (Maybe Text)
launchTemplatePlacement_hostResourceGroupArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplatePlacement' {Maybe Text
hostResourceGroupArn :: Maybe Text
$sel:hostResourceGroupArn:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Text
hostResourceGroupArn} -> Maybe Text
hostResourceGroupArn) (\s :: LaunchTemplatePlacement
s@LaunchTemplatePlacement' {} Maybe Text
a -> LaunchTemplatePlacement
s {$sel:hostResourceGroupArn:LaunchTemplatePlacement' :: Maybe Text
hostResourceGroupArn = Maybe Text
a} :: LaunchTemplatePlacement)

-- | The number of the partition the instance should launch in. Valid only if
-- the placement group strategy is set to @partition@.
launchTemplatePlacement_partitionNumber :: Lens.Lens' LaunchTemplatePlacement (Prelude.Maybe Prelude.Int)
launchTemplatePlacement_partitionNumber :: Lens' LaunchTemplatePlacement (Maybe Int)
launchTemplatePlacement_partitionNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplatePlacement' {Maybe Int
partitionNumber :: Maybe Int
$sel:partitionNumber:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Int
partitionNumber} -> Maybe Int
partitionNumber) (\s :: LaunchTemplatePlacement
s@LaunchTemplatePlacement' {} Maybe Int
a -> LaunchTemplatePlacement
s {$sel:partitionNumber:LaunchTemplatePlacement' :: Maybe Int
partitionNumber = Maybe Int
a} :: LaunchTemplatePlacement)

-- | Reserved for future use.
launchTemplatePlacement_spreadDomain :: Lens.Lens' LaunchTemplatePlacement (Prelude.Maybe Prelude.Text)
launchTemplatePlacement_spreadDomain :: Lens' LaunchTemplatePlacement (Maybe Text)
launchTemplatePlacement_spreadDomain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplatePlacement' {Maybe Text
spreadDomain :: Maybe Text
$sel:spreadDomain:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Text
spreadDomain} -> Maybe Text
spreadDomain) (\s :: LaunchTemplatePlacement
s@LaunchTemplatePlacement' {} Maybe Text
a -> LaunchTemplatePlacement
s {$sel:spreadDomain:LaunchTemplatePlacement' :: Maybe Text
spreadDomain = Maybe Text
a} :: LaunchTemplatePlacement)

-- | The tenancy of the instance (if the instance is running in a VPC). An
-- instance with a tenancy of @dedicated@ runs on single-tenant hardware.
launchTemplatePlacement_tenancy :: Lens.Lens' LaunchTemplatePlacement (Prelude.Maybe Tenancy)
launchTemplatePlacement_tenancy :: Lens' LaunchTemplatePlacement (Maybe Tenancy)
launchTemplatePlacement_tenancy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\LaunchTemplatePlacement' {Maybe Tenancy
tenancy :: Maybe Tenancy
$sel:tenancy:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Tenancy
tenancy} -> Maybe Tenancy
tenancy) (\s :: LaunchTemplatePlacement
s@LaunchTemplatePlacement' {} Maybe Tenancy
a -> LaunchTemplatePlacement
s {$sel:tenancy:LaunchTemplatePlacement' :: Maybe Tenancy
tenancy = Maybe Tenancy
a} :: LaunchTemplatePlacement)

instance Data.FromXML LaunchTemplatePlacement where
  parseXML :: [Node] -> Either String LaunchTemplatePlacement
parseXML [Node]
x =
    Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Tenancy
-> LaunchTemplatePlacement
LaunchTemplatePlacement'
      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
"affinity")
      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
"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 (Maybe a)
Data..@? Text
"groupId")
      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
"groupName")
      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
"hostId")
      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
"hostResourceGroupArn")
      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
"partitionNumber")
      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
"spreadDomain")
      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
"tenancy")

instance Prelude.Hashable LaunchTemplatePlacement where
  hashWithSalt :: Int -> LaunchTemplatePlacement -> Int
hashWithSalt Int
_salt LaunchTemplatePlacement' {Maybe Int
Maybe Text
Maybe Tenancy
tenancy :: Maybe Tenancy
spreadDomain :: Maybe Text
partitionNumber :: Maybe Int
hostResourceGroupArn :: Maybe Text
hostId :: Maybe Text
groupName :: Maybe Text
groupId :: Maybe Text
availabilityZone :: Maybe Text
affinity :: Maybe Text
$sel:tenancy:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Tenancy
$sel:spreadDomain:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Text
$sel:partitionNumber:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Int
$sel:hostResourceGroupArn:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Text
$sel:hostId:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Text
$sel:groupName:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Text
$sel:groupId:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Text
$sel:availabilityZone:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Text
$sel:affinity:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
affinity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
availabilityZone
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
groupId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
groupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
hostId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
hostResourceGroupArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
partitionNumber
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
spreadDomain
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Tenancy
tenancy

instance Prelude.NFData LaunchTemplatePlacement where
  rnf :: LaunchTemplatePlacement -> ()
rnf LaunchTemplatePlacement' {Maybe Int
Maybe Text
Maybe Tenancy
tenancy :: Maybe Tenancy
spreadDomain :: Maybe Text
partitionNumber :: Maybe Int
hostResourceGroupArn :: Maybe Text
hostId :: Maybe Text
groupName :: Maybe Text
groupId :: Maybe Text
availabilityZone :: Maybe Text
affinity :: Maybe Text
$sel:tenancy:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Tenancy
$sel:spreadDomain:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Text
$sel:partitionNumber:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Int
$sel:hostResourceGroupArn:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Text
$sel:hostId:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Text
$sel:groupName:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Text
$sel:groupId:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Text
$sel:availabilityZone:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Text
$sel:affinity:LaunchTemplatePlacement' :: LaunchTemplatePlacement -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
affinity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
availabilityZone
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
groupId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
groupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
hostId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
hostResourceGroupArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
partitionNumber
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
spreadDomain
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Tenancy
tenancy