{-# 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.GameLift.Types.FleetAttributes
-- 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.GameLift.Types.FleetAttributes where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.GameLift.Types.AnywhereConfiguration
import Amazonka.GameLift.Types.CertificateConfiguration
import Amazonka.GameLift.Types.ComputeType
import Amazonka.GameLift.Types.EC2InstanceType
import Amazonka.GameLift.Types.FleetAction
import Amazonka.GameLift.Types.FleetStatus
import Amazonka.GameLift.Types.FleetType
import Amazonka.GameLift.Types.OperatingSystem
import Amazonka.GameLift.Types.ProtectionPolicy
import Amazonka.GameLift.Types.ResourceCreationLimitPolicy
import qualified Amazonka.Prelude as Prelude

-- | Describes a GameLift fleet of game hosting resources.
--
-- __Related actions__
--
-- /See:/ 'newFleetAttributes' smart constructor.
data FleetAttributes = FleetAttributes'
  { FleetAttributes -> Maybe AnywhereConfiguration
anywhereConfiguration :: Prelude.Maybe AnywhereConfiguration,
    -- | The Amazon Resource Name
    -- (<https://docs.aws.amazon.com/AmazonS3/latest/dev/s3-arn-format.html ARN>)
    -- associated with the GameLift build resource that is deployed on
    -- instances in this fleet. In a GameLift build ARN, the resource ID
    -- matches the @BuildId@ value.
    FleetAttributes -> Maybe Text
buildArn :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the build resource that is deployed on instances
    -- in this fleet.
    FleetAttributes -> Maybe Text
buildId :: Prelude.Maybe Prelude.Text,
    FleetAttributes -> Maybe CertificateConfiguration
certificateConfiguration :: Prelude.Maybe CertificateConfiguration,
    -- | The type of compute resource used to host your game servers. You can use
    -- your own compute resources with GameLift Anywhere or use Amazon EC2
    -- instances with managed GameLift.
    FleetAttributes -> Maybe ComputeType
computeType :: Prelude.Maybe ComputeType,
    -- | A time stamp indicating when this data object was created. Format is a
    -- number expressed in Unix time as milliseconds (for example
    -- @\"1469498468.057\"@).
    FleetAttributes -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | A human-readable description of the fleet.
    FleetAttributes -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name
    -- (<https://docs.aws.amazon.com/AmazonS3/latest/dev/s3-arn-format.html ARN>)
    -- that is assigned to a GameLift fleet resource and uniquely identifies
    -- it. ARNs are unique across all Regions. Format is
    -- @arn:aws:gamelift:\<region>::fleet\/fleet-a1234567-b8c9-0d1e-2fa3-b45c6d7e8912@.
    -- In a GameLift fleet ARN, the resource ID matches the @FleetId@ value.
    FleetAttributes -> Maybe Text
fleetArn :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the fleet.
    FleetAttributes -> Maybe Text
fleetId :: Prelude.Maybe Prelude.Text,
    -- | Indicates whether to use On-Demand or Spot instances for this fleet. By
    -- default, this property is set to @ON_DEMAND@. Learn more about when to
    -- use
    -- <https://docs.aws.amazon.com/gamelift/latest/developerguide/gamelift-ec2-instances.html#gamelift-ec2-instances-spot On-Demand versus Spot Instances>.
    -- This property cannot be changed after the fleet is created.
    FleetAttributes -> Maybe FleetType
fleetType :: Prelude.Maybe FleetType,
    -- | A unique identifier for an IAM role that manages access to your Amazon
    -- Web Services services. With an instance role ARN set, any application
    -- that runs on an instance in this fleet can assume the role, including
    -- install scripts, server processes, and daemons (background processes).
    -- Create a role or look up a role\'s ARN by using the
    -- <https://console.aws.amazon.com/iam/ IAM dashboard> in the Amazon Web
    -- Services Management Console. Learn more about using on-box credentials
    -- for your game servers at
    -- <https://docs.aws.amazon.com/gamelift/latest/developerguide/gamelift-sdk-server-resources.html Access external resources from a game server>.
    FleetAttributes -> Maybe Text
instanceRoleArn :: Prelude.Maybe Prelude.Text,
    -- | The Amazon EC2 instance type that determines the computing resources of
    -- each instance in the fleet. Instance type defines the CPU, memory,
    -- storage, and networking capacity. See
    -- <http://aws.amazon.com/ec2/instance-types/ Amazon Elastic Compute Cloud Instance Types>
    -- for detailed descriptions.
    FleetAttributes -> Maybe EC2InstanceType
instanceType :: Prelude.Maybe EC2InstanceType,
    -- | __This parameter is no longer used.__ Game session log paths are now
    -- defined using the GameLift server API @ProcessReady()@ @logParameters@.
    -- See more information in the
    -- <https://docs.aws.amazon.com/gamelift/latest/developerguide/gamelift-sdk-server-api-ref.html#gamelift-sdk-server-api-ref-dataypes-process Server API Reference>.
    FleetAttributes -> Maybe [Text]
logPaths :: Prelude.Maybe [Prelude.Text],
    -- | Name of a metric group that metrics for this fleet are added to. In
    -- Amazon CloudWatch, you can view aggregated metrics for fleets that are
    -- in a metric group. A fleet can be included in only one metric group at a
    -- time.
    FleetAttributes -> Maybe [Text]
metricGroups :: Prelude.Maybe [Prelude.Text],
    -- | A descriptive label that is associated with a fleet. Fleet names do not
    -- need to be unique.
    FleetAttributes -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The type of game session protection to set on all new instances that are
    -- started in the fleet.
    --
    -- -   __NoProtection__ -- The game session can be terminated during a
    --     scale-down event.
    --
    -- -   __FullProtection__ -- If the game session is in an @ACTIVE@ status,
    --     it cannot be terminated during a scale-down event.
    FleetAttributes -> Maybe ProtectionPolicy
newGameSessionProtectionPolicy' :: Prelude.Maybe ProtectionPolicy,
    -- | The operating system of the fleet\'s computing resources. A fleet\'s
    -- operating system is determined by the OS of the build or script that is
    -- deployed on this fleet.
    FleetAttributes -> Maybe OperatingSystem
operatingSystem :: Prelude.Maybe OperatingSystem,
    FleetAttributes -> Maybe ResourceCreationLimitPolicy
resourceCreationLimitPolicy :: Prelude.Maybe ResourceCreationLimitPolicy,
    -- | The Amazon Resource Name
    -- (<https://docs.aws.amazon.com/AmazonS3/latest/dev/s3-arn-format.html ARN>)
    -- associated with the GameLift script resource that is deployed on
    -- instances in this fleet. In a GameLift script ARN, the resource ID
    -- matches the @ScriptId@ value.
    FleetAttributes -> Maybe Text
scriptArn :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the Realtime script resource that is deployed on
    -- instances in this fleet.
    FleetAttributes -> Maybe Text
scriptId :: Prelude.Maybe Prelude.Text,
    -- | __This parameter is no longer used.__ Server launch parameters are now
    -- defined using the fleet\'s runtime configuration . Requests that use
    -- this parameter instead continue to be valid.
    FleetAttributes -> Maybe Text
serverLaunchParameters :: Prelude.Maybe Prelude.Text,
    -- | __This parameter is no longer used.__ Server launch paths are now
    -- defined using the fleet\'s
    -- <https://docs.aws.amazon.com/gamelift/latest/apireference/RuntimeConfiguration.html RuntimeConfiguration>
    -- . Requests that use this parameter instead continue to be valid.
    FleetAttributes -> Maybe Text
serverLaunchPath :: Prelude.Maybe Prelude.Text,
    -- | Current status of the fleet. Possible fleet statuses include the
    -- following:
    --
    -- -   __NEW__ -- A new fleet has been defined and desired instances is set
    --     to 1.
    --
    -- -   __DOWNLOADING\/VALIDATING\/BUILDING\/ACTIVATING__ -- GameLift is
    --     setting up the new fleet, creating new instances with the game build
    --     or Realtime script and starting server processes.
    --
    -- -   __ACTIVE__ -- Hosts can now accept game sessions.
    --
    -- -   __ERROR__ -- An error occurred when downloading, validating,
    --     building, or activating the fleet.
    --
    -- -   __DELETING__ -- Hosts are responding to a delete fleet request.
    --
    -- -   __TERMINATED__ -- The fleet no longer exists.
    FleetAttributes -> Maybe FleetStatus
status :: Prelude.Maybe FleetStatus,
    -- | A list of fleet activity that has been suspended using
    -- <https://docs.aws.amazon.com/gamelift/latest/apireference/API_StopFleetActions.html StopFleetActions>
    -- . This includes fleet auto-scaling.
    FleetAttributes -> Maybe (NonEmpty FleetAction)
stoppedActions :: Prelude.Maybe (Prelude.NonEmpty FleetAction),
    -- | A time stamp indicating when this data object was terminated. Format is
    -- a number expressed in Unix time as milliseconds (for example
    -- @\"1469498468.057\"@).
    FleetAttributes -> Maybe POSIX
terminationTime :: Prelude.Maybe Data.POSIX
  }
  deriving (FleetAttributes -> FleetAttributes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FleetAttributes -> FleetAttributes -> Bool
$c/= :: FleetAttributes -> FleetAttributes -> Bool
== :: FleetAttributes -> FleetAttributes -> Bool
$c== :: FleetAttributes -> FleetAttributes -> Bool
Prelude.Eq, ReadPrec [FleetAttributes]
ReadPrec FleetAttributes
Int -> ReadS FleetAttributes
ReadS [FleetAttributes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FleetAttributes]
$creadListPrec :: ReadPrec [FleetAttributes]
readPrec :: ReadPrec FleetAttributes
$creadPrec :: ReadPrec FleetAttributes
readList :: ReadS [FleetAttributes]
$creadList :: ReadS [FleetAttributes]
readsPrec :: Int -> ReadS FleetAttributes
$creadsPrec :: Int -> ReadS FleetAttributes
Prelude.Read, Int -> FleetAttributes -> ShowS
[FleetAttributes] -> ShowS
FleetAttributes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FleetAttributes] -> ShowS
$cshowList :: [FleetAttributes] -> ShowS
show :: FleetAttributes -> String
$cshow :: FleetAttributes -> String
showsPrec :: Int -> FleetAttributes -> ShowS
$cshowsPrec :: Int -> FleetAttributes -> ShowS
Prelude.Show, forall x. Rep FleetAttributes x -> FleetAttributes
forall x. FleetAttributes -> Rep FleetAttributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FleetAttributes x -> FleetAttributes
$cfrom :: forall x. FleetAttributes -> Rep FleetAttributes x
Prelude.Generic)

-- |
-- Create a value of 'FleetAttributes' 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:
--
-- 'anywhereConfiguration', 'fleetAttributes_anywhereConfiguration' - Undocumented member.
--
-- 'buildArn', 'fleetAttributes_buildArn' - The Amazon Resource Name
-- (<https://docs.aws.amazon.com/AmazonS3/latest/dev/s3-arn-format.html ARN>)
-- associated with the GameLift build resource that is deployed on
-- instances in this fleet. In a GameLift build ARN, the resource ID
-- matches the @BuildId@ value.
--
-- 'buildId', 'fleetAttributes_buildId' - A unique identifier for the build resource that is deployed on instances
-- in this fleet.
--
-- 'certificateConfiguration', 'fleetAttributes_certificateConfiguration' - Undocumented member.
--
-- 'computeType', 'fleetAttributes_computeType' - The type of compute resource used to host your game servers. You can use
-- your own compute resources with GameLift Anywhere or use Amazon EC2
-- instances with managed GameLift.
--
-- 'creationTime', 'fleetAttributes_creationTime' - A time stamp indicating when this data object was created. Format is a
-- number expressed in Unix time as milliseconds (for example
-- @\"1469498468.057\"@).
--
-- 'description', 'fleetAttributes_description' - A human-readable description of the fleet.
--
-- 'fleetArn', 'fleetAttributes_fleetArn' - The Amazon Resource Name
-- (<https://docs.aws.amazon.com/AmazonS3/latest/dev/s3-arn-format.html ARN>)
-- that is assigned to a GameLift fleet resource and uniquely identifies
-- it. ARNs are unique across all Regions. Format is
-- @arn:aws:gamelift:\<region>::fleet\/fleet-a1234567-b8c9-0d1e-2fa3-b45c6d7e8912@.
-- In a GameLift fleet ARN, the resource ID matches the @FleetId@ value.
--
-- 'fleetId', 'fleetAttributes_fleetId' - A unique identifier for the fleet.
--
-- 'fleetType', 'fleetAttributes_fleetType' - Indicates whether to use On-Demand or Spot instances for this fleet. By
-- default, this property is set to @ON_DEMAND@. Learn more about when to
-- use
-- <https://docs.aws.amazon.com/gamelift/latest/developerguide/gamelift-ec2-instances.html#gamelift-ec2-instances-spot On-Demand versus Spot Instances>.
-- This property cannot be changed after the fleet is created.
--
-- 'instanceRoleArn', 'fleetAttributes_instanceRoleArn' - A unique identifier for an IAM role that manages access to your Amazon
-- Web Services services. With an instance role ARN set, any application
-- that runs on an instance in this fleet can assume the role, including
-- install scripts, server processes, and daemons (background processes).
-- Create a role or look up a role\'s ARN by using the
-- <https://console.aws.amazon.com/iam/ IAM dashboard> in the Amazon Web
-- Services Management Console. Learn more about using on-box credentials
-- for your game servers at
-- <https://docs.aws.amazon.com/gamelift/latest/developerguide/gamelift-sdk-server-resources.html Access external resources from a game server>.
--
-- 'instanceType', 'fleetAttributes_instanceType' - The Amazon EC2 instance type that determines the computing resources of
-- each instance in the fleet. Instance type defines the CPU, memory,
-- storage, and networking capacity. See
-- <http://aws.amazon.com/ec2/instance-types/ Amazon Elastic Compute Cloud Instance Types>
-- for detailed descriptions.
--
-- 'logPaths', 'fleetAttributes_logPaths' - __This parameter is no longer used.__ Game session log paths are now
-- defined using the GameLift server API @ProcessReady()@ @logParameters@.
-- See more information in the
-- <https://docs.aws.amazon.com/gamelift/latest/developerguide/gamelift-sdk-server-api-ref.html#gamelift-sdk-server-api-ref-dataypes-process Server API Reference>.
--
-- 'metricGroups', 'fleetAttributes_metricGroups' - Name of a metric group that metrics for this fleet are added to. In
-- Amazon CloudWatch, you can view aggregated metrics for fleets that are
-- in a metric group. A fleet can be included in only one metric group at a
-- time.
--
-- 'name', 'fleetAttributes_name' - A descriptive label that is associated with a fleet. Fleet names do not
-- need to be unique.
--
-- 'newGameSessionProtectionPolicy'', 'fleetAttributes_newGameSessionProtectionPolicy' - The type of game session protection to set on all new instances that are
-- started in the fleet.
--
-- -   __NoProtection__ -- The game session can be terminated during a
--     scale-down event.
--
-- -   __FullProtection__ -- If the game session is in an @ACTIVE@ status,
--     it cannot be terminated during a scale-down event.
--
-- 'operatingSystem', 'fleetAttributes_operatingSystem' - The operating system of the fleet\'s computing resources. A fleet\'s
-- operating system is determined by the OS of the build or script that is
-- deployed on this fleet.
--
-- 'resourceCreationLimitPolicy', 'fleetAttributes_resourceCreationLimitPolicy' - Undocumented member.
--
-- 'scriptArn', 'fleetAttributes_scriptArn' - The Amazon Resource Name
-- (<https://docs.aws.amazon.com/AmazonS3/latest/dev/s3-arn-format.html ARN>)
-- associated with the GameLift script resource that is deployed on
-- instances in this fleet. In a GameLift script ARN, the resource ID
-- matches the @ScriptId@ value.
--
-- 'scriptId', 'fleetAttributes_scriptId' - A unique identifier for the Realtime script resource that is deployed on
-- instances in this fleet.
--
-- 'serverLaunchParameters', 'fleetAttributes_serverLaunchParameters' - __This parameter is no longer used.__ Server launch parameters are now
-- defined using the fleet\'s runtime configuration . Requests that use
-- this parameter instead continue to be valid.
--
-- 'serverLaunchPath', 'fleetAttributes_serverLaunchPath' - __This parameter is no longer used.__ Server launch paths are now
-- defined using the fleet\'s
-- <https://docs.aws.amazon.com/gamelift/latest/apireference/RuntimeConfiguration.html RuntimeConfiguration>
-- . Requests that use this parameter instead continue to be valid.
--
-- 'status', 'fleetAttributes_status' - Current status of the fleet. Possible fleet statuses include the
-- following:
--
-- -   __NEW__ -- A new fleet has been defined and desired instances is set
--     to 1.
--
-- -   __DOWNLOADING\/VALIDATING\/BUILDING\/ACTIVATING__ -- GameLift is
--     setting up the new fleet, creating new instances with the game build
--     or Realtime script and starting server processes.
--
-- -   __ACTIVE__ -- Hosts can now accept game sessions.
--
-- -   __ERROR__ -- An error occurred when downloading, validating,
--     building, or activating the fleet.
--
-- -   __DELETING__ -- Hosts are responding to a delete fleet request.
--
-- -   __TERMINATED__ -- The fleet no longer exists.
--
-- 'stoppedActions', 'fleetAttributes_stoppedActions' - A list of fleet activity that has been suspended using
-- <https://docs.aws.amazon.com/gamelift/latest/apireference/API_StopFleetActions.html StopFleetActions>
-- . This includes fleet auto-scaling.
--
-- 'terminationTime', 'fleetAttributes_terminationTime' - A time stamp indicating when this data object was terminated. Format is
-- a number expressed in Unix time as milliseconds (for example
-- @\"1469498468.057\"@).
newFleetAttributes ::
  FleetAttributes
newFleetAttributes :: FleetAttributes
newFleetAttributes =
  FleetAttributes'
    { $sel:anywhereConfiguration:FleetAttributes' :: Maybe AnywhereConfiguration
anywhereConfiguration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:buildArn:FleetAttributes' :: Maybe Text
buildArn = forall a. Maybe a
Prelude.Nothing,
      $sel:buildId:FleetAttributes' :: Maybe Text
buildId = forall a. Maybe a
Prelude.Nothing,
      $sel:certificateConfiguration:FleetAttributes' :: Maybe CertificateConfiguration
certificateConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:computeType:FleetAttributes' :: Maybe ComputeType
computeType = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:FleetAttributes' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:description:FleetAttributes' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:fleetArn:FleetAttributes' :: Maybe Text
fleetArn = forall a. Maybe a
Prelude.Nothing,
      $sel:fleetId:FleetAttributes' :: Maybe Text
fleetId = forall a. Maybe a
Prelude.Nothing,
      $sel:fleetType:FleetAttributes' :: Maybe FleetType
fleetType = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceRoleArn:FleetAttributes' :: Maybe Text
instanceRoleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceType:FleetAttributes' :: Maybe EC2InstanceType
instanceType = forall a. Maybe a
Prelude.Nothing,
      $sel:logPaths:FleetAttributes' :: Maybe [Text]
logPaths = forall a. Maybe a
Prelude.Nothing,
      $sel:metricGroups:FleetAttributes' :: Maybe [Text]
metricGroups = forall a. Maybe a
Prelude.Nothing,
      $sel:name:FleetAttributes' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:newGameSessionProtectionPolicy':FleetAttributes' :: Maybe ProtectionPolicy
newGameSessionProtectionPolicy' = forall a. Maybe a
Prelude.Nothing,
      $sel:operatingSystem:FleetAttributes' :: Maybe OperatingSystem
operatingSystem = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceCreationLimitPolicy:FleetAttributes' :: Maybe ResourceCreationLimitPolicy
resourceCreationLimitPolicy = forall a. Maybe a
Prelude.Nothing,
      $sel:scriptArn:FleetAttributes' :: Maybe Text
scriptArn = forall a. Maybe a
Prelude.Nothing,
      $sel:scriptId:FleetAttributes' :: Maybe Text
scriptId = forall a. Maybe a
Prelude.Nothing,
      $sel:serverLaunchParameters:FleetAttributes' :: Maybe Text
serverLaunchParameters = forall a. Maybe a
Prelude.Nothing,
      $sel:serverLaunchPath:FleetAttributes' :: Maybe Text
serverLaunchPath = forall a. Maybe a
Prelude.Nothing,
      $sel:status:FleetAttributes' :: Maybe FleetStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:stoppedActions:FleetAttributes' :: Maybe (NonEmpty FleetAction)
stoppedActions = forall a. Maybe a
Prelude.Nothing,
      $sel:terminationTime:FleetAttributes' :: Maybe POSIX
terminationTime = forall a. Maybe a
Prelude.Nothing
    }

-- | Undocumented member.
fleetAttributes_anywhereConfiguration :: Lens.Lens' FleetAttributes (Prelude.Maybe AnywhereConfiguration)
fleetAttributes_anywhereConfiguration :: Lens' FleetAttributes (Maybe AnywhereConfiguration)
fleetAttributes_anywhereConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe AnywhereConfiguration
anywhereConfiguration :: Maybe AnywhereConfiguration
$sel:anywhereConfiguration:FleetAttributes' :: FleetAttributes -> Maybe AnywhereConfiguration
anywhereConfiguration} -> Maybe AnywhereConfiguration
anywhereConfiguration) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe AnywhereConfiguration
a -> FleetAttributes
s {$sel:anywhereConfiguration:FleetAttributes' :: Maybe AnywhereConfiguration
anywhereConfiguration = Maybe AnywhereConfiguration
a} :: FleetAttributes)

-- | The Amazon Resource Name
-- (<https://docs.aws.amazon.com/AmazonS3/latest/dev/s3-arn-format.html ARN>)
-- associated with the GameLift build resource that is deployed on
-- instances in this fleet. In a GameLift build ARN, the resource ID
-- matches the @BuildId@ value.
fleetAttributes_buildArn :: Lens.Lens' FleetAttributes (Prelude.Maybe Prelude.Text)
fleetAttributes_buildArn :: Lens' FleetAttributes (Maybe Text)
fleetAttributes_buildArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe Text
buildArn :: Maybe Text
$sel:buildArn:FleetAttributes' :: FleetAttributes -> Maybe Text
buildArn} -> Maybe Text
buildArn) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe Text
a -> FleetAttributes
s {$sel:buildArn:FleetAttributes' :: Maybe Text
buildArn = Maybe Text
a} :: FleetAttributes)

-- | A unique identifier for the build resource that is deployed on instances
-- in this fleet.
fleetAttributes_buildId :: Lens.Lens' FleetAttributes (Prelude.Maybe Prelude.Text)
fleetAttributes_buildId :: Lens' FleetAttributes (Maybe Text)
fleetAttributes_buildId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe Text
buildId :: Maybe Text
$sel:buildId:FleetAttributes' :: FleetAttributes -> Maybe Text
buildId} -> Maybe Text
buildId) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe Text
a -> FleetAttributes
s {$sel:buildId:FleetAttributes' :: Maybe Text
buildId = Maybe Text
a} :: FleetAttributes)

-- | Undocumented member.
fleetAttributes_certificateConfiguration :: Lens.Lens' FleetAttributes (Prelude.Maybe CertificateConfiguration)
fleetAttributes_certificateConfiguration :: Lens' FleetAttributes (Maybe CertificateConfiguration)
fleetAttributes_certificateConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe CertificateConfiguration
certificateConfiguration :: Maybe CertificateConfiguration
$sel:certificateConfiguration:FleetAttributes' :: FleetAttributes -> Maybe CertificateConfiguration
certificateConfiguration} -> Maybe CertificateConfiguration
certificateConfiguration) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe CertificateConfiguration
a -> FleetAttributes
s {$sel:certificateConfiguration:FleetAttributes' :: Maybe CertificateConfiguration
certificateConfiguration = Maybe CertificateConfiguration
a} :: FleetAttributes)

-- | The type of compute resource used to host your game servers. You can use
-- your own compute resources with GameLift Anywhere or use Amazon EC2
-- instances with managed GameLift.
fleetAttributes_computeType :: Lens.Lens' FleetAttributes (Prelude.Maybe ComputeType)
fleetAttributes_computeType :: Lens' FleetAttributes (Maybe ComputeType)
fleetAttributes_computeType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe ComputeType
computeType :: Maybe ComputeType
$sel:computeType:FleetAttributes' :: FleetAttributes -> Maybe ComputeType
computeType} -> Maybe ComputeType
computeType) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe ComputeType
a -> FleetAttributes
s {$sel:computeType:FleetAttributes' :: Maybe ComputeType
computeType = Maybe ComputeType
a} :: FleetAttributes)

-- | A time stamp indicating when this data object was created. Format is a
-- number expressed in Unix time as milliseconds (for example
-- @\"1469498468.057\"@).
fleetAttributes_creationTime :: Lens.Lens' FleetAttributes (Prelude.Maybe Prelude.UTCTime)
fleetAttributes_creationTime :: Lens' FleetAttributes (Maybe UTCTime)
fleetAttributes_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:FleetAttributes' :: FleetAttributes -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe POSIX
a -> FleetAttributes
s {$sel:creationTime:FleetAttributes' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: FleetAttributes) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | A human-readable description of the fleet.
fleetAttributes_description :: Lens.Lens' FleetAttributes (Prelude.Maybe Prelude.Text)
fleetAttributes_description :: Lens' FleetAttributes (Maybe Text)
fleetAttributes_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe Text
description :: Maybe Text
$sel:description:FleetAttributes' :: FleetAttributes -> Maybe Text
description} -> Maybe Text
description) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe Text
a -> FleetAttributes
s {$sel:description:FleetAttributes' :: Maybe Text
description = Maybe Text
a} :: FleetAttributes)

-- | The Amazon Resource Name
-- (<https://docs.aws.amazon.com/AmazonS3/latest/dev/s3-arn-format.html ARN>)
-- that is assigned to a GameLift fleet resource and uniquely identifies
-- it. ARNs are unique across all Regions. Format is
-- @arn:aws:gamelift:\<region>::fleet\/fleet-a1234567-b8c9-0d1e-2fa3-b45c6d7e8912@.
-- In a GameLift fleet ARN, the resource ID matches the @FleetId@ value.
fleetAttributes_fleetArn :: Lens.Lens' FleetAttributes (Prelude.Maybe Prelude.Text)
fleetAttributes_fleetArn :: Lens' FleetAttributes (Maybe Text)
fleetAttributes_fleetArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe Text
fleetArn :: Maybe Text
$sel:fleetArn:FleetAttributes' :: FleetAttributes -> Maybe Text
fleetArn} -> Maybe Text
fleetArn) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe Text
a -> FleetAttributes
s {$sel:fleetArn:FleetAttributes' :: Maybe Text
fleetArn = Maybe Text
a} :: FleetAttributes)

-- | A unique identifier for the fleet.
fleetAttributes_fleetId :: Lens.Lens' FleetAttributes (Prelude.Maybe Prelude.Text)
fleetAttributes_fleetId :: Lens' FleetAttributes (Maybe Text)
fleetAttributes_fleetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe Text
fleetId :: Maybe Text
$sel:fleetId:FleetAttributes' :: FleetAttributes -> Maybe Text
fleetId} -> Maybe Text
fleetId) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe Text
a -> FleetAttributes
s {$sel:fleetId:FleetAttributes' :: Maybe Text
fleetId = Maybe Text
a} :: FleetAttributes)

-- | Indicates whether to use On-Demand or Spot instances for this fleet. By
-- default, this property is set to @ON_DEMAND@. Learn more about when to
-- use
-- <https://docs.aws.amazon.com/gamelift/latest/developerguide/gamelift-ec2-instances.html#gamelift-ec2-instances-spot On-Demand versus Spot Instances>.
-- This property cannot be changed after the fleet is created.
fleetAttributes_fleetType :: Lens.Lens' FleetAttributes (Prelude.Maybe FleetType)
fleetAttributes_fleetType :: Lens' FleetAttributes (Maybe FleetType)
fleetAttributes_fleetType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe FleetType
fleetType :: Maybe FleetType
$sel:fleetType:FleetAttributes' :: FleetAttributes -> Maybe FleetType
fleetType} -> Maybe FleetType
fleetType) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe FleetType
a -> FleetAttributes
s {$sel:fleetType:FleetAttributes' :: Maybe FleetType
fleetType = Maybe FleetType
a} :: FleetAttributes)

-- | A unique identifier for an IAM role that manages access to your Amazon
-- Web Services services. With an instance role ARN set, any application
-- that runs on an instance in this fleet can assume the role, including
-- install scripts, server processes, and daemons (background processes).
-- Create a role or look up a role\'s ARN by using the
-- <https://console.aws.amazon.com/iam/ IAM dashboard> in the Amazon Web
-- Services Management Console. Learn more about using on-box credentials
-- for your game servers at
-- <https://docs.aws.amazon.com/gamelift/latest/developerguide/gamelift-sdk-server-resources.html Access external resources from a game server>.
fleetAttributes_instanceRoleArn :: Lens.Lens' FleetAttributes (Prelude.Maybe Prelude.Text)
fleetAttributes_instanceRoleArn :: Lens' FleetAttributes (Maybe Text)
fleetAttributes_instanceRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe Text
instanceRoleArn :: Maybe Text
$sel:instanceRoleArn:FleetAttributes' :: FleetAttributes -> Maybe Text
instanceRoleArn} -> Maybe Text
instanceRoleArn) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe Text
a -> FleetAttributes
s {$sel:instanceRoleArn:FleetAttributes' :: Maybe Text
instanceRoleArn = Maybe Text
a} :: FleetAttributes)

-- | The Amazon EC2 instance type that determines the computing resources of
-- each instance in the fleet. Instance type defines the CPU, memory,
-- storage, and networking capacity. See
-- <http://aws.amazon.com/ec2/instance-types/ Amazon Elastic Compute Cloud Instance Types>
-- for detailed descriptions.
fleetAttributes_instanceType :: Lens.Lens' FleetAttributes (Prelude.Maybe EC2InstanceType)
fleetAttributes_instanceType :: Lens' FleetAttributes (Maybe EC2InstanceType)
fleetAttributes_instanceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe EC2InstanceType
instanceType :: Maybe EC2InstanceType
$sel:instanceType:FleetAttributes' :: FleetAttributes -> Maybe EC2InstanceType
instanceType} -> Maybe EC2InstanceType
instanceType) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe EC2InstanceType
a -> FleetAttributes
s {$sel:instanceType:FleetAttributes' :: Maybe EC2InstanceType
instanceType = Maybe EC2InstanceType
a} :: FleetAttributes)

-- | __This parameter is no longer used.__ Game session log paths are now
-- defined using the GameLift server API @ProcessReady()@ @logParameters@.
-- See more information in the
-- <https://docs.aws.amazon.com/gamelift/latest/developerguide/gamelift-sdk-server-api-ref.html#gamelift-sdk-server-api-ref-dataypes-process Server API Reference>.
fleetAttributes_logPaths :: Lens.Lens' FleetAttributes (Prelude.Maybe [Prelude.Text])
fleetAttributes_logPaths :: Lens' FleetAttributes (Maybe [Text])
fleetAttributes_logPaths = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe [Text]
logPaths :: Maybe [Text]
$sel:logPaths:FleetAttributes' :: FleetAttributes -> Maybe [Text]
logPaths} -> Maybe [Text]
logPaths) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe [Text]
a -> FleetAttributes
s {$sel:logPaths:FleetAttributes' :: Maybe [Text]
logPaths = Maybe [Text]
a} :: FleetAttributes) 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

-- | Name of a metric group that metrics for this fleet are added to. In
-- Amazon CloudWatch, you can view aggregated metrics for fleets that are
-- in a metric group. A fleet can be included in only one metric group at a
-- time.
fleetAttributes_metricGroups :: Lens.Lens' FleetAttributes (Prelude.Maybe [Prelude.Text])
fleetAttributes_metricGroups :: Lens' FleetAttributes (Maybe [Text])
fleetAttributes_metricGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe [Text]
metricGroups :: Maybe [Text]
$sel:metricGroups:FleetAttributes' :: FleetAttributes -> Maybe [Text]
metricGroups} -> Maybe [Text]
metricGroups) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe [Text]
a -> FleetAttributes
s {$sel:metricGroups:FleetAttributes' :: Maybe [Text]
metricGroups = Maybe [Text]
a} :: FleetAttributes) 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

-- | A descriptive label that is associated with a fleet. Fleet names do not
-- need to be unique.
fleetAttributes_name :: Lens.Lens' FleetAttributes (Prelude.Maybe Prelude.Text)
fleetAttributes_name :: Lens' FleetAttributes (Maybe Text)
fleetAttributes_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe Text
name :: Maybe Text
$sel:name:FleetAttributes' :: FleetAttributes -> Maybe Text
name} -> Maybe Text
name) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe Text
a -> FleetAttributes
s {$sel:name:FleetAttributes' :: Maybe Text
name = Maybe Text
a} :: FleetAttributes)

-- | The type of game session protection to set on all new instances that are
-- started in the fleet.
--
-- -   __NoProtection__ -- The game session can be terminated during a
--     scale-down event.
--
-- -   __FullProtection__ -- If the game session is in an @ACTIVE@ status,
--     it cannot be terminated during a scale-down event.
fleetAttributes_newGameSessionProtectionPolicy :: Lens.Lens' FleetAttributes (Prelude.Maybe ProtectionPolicy)
fleetAttributes_newGameSessionProtectionPolicy :: Lens' FleetAttributes (Maybe ProtectionPolicy)
fleetAttributes_newGameSessionProtectionPolicy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe ProtectionPolicy
newGameSessionProtectionPolicy' :: Maybe ProtectionPolicy
$sel:newGameSessionProtectionPolicy':FleetAttributes' :: FleetAttributes -> Maybe ProtectionPolicy
newGameSessionProtectionPolicy'} -> Maybe ProtectionPolicy
newGameSessionProtectionPolicy') (\s :: FleetAttributes
s@FleetAttributes' {} Maybe ProtectionPolicy
a -> FleetAttributes
s {$sel:newGameSessionProtectionPolicy':FleetAttributes' :: Maybe ProtectionPolicy
newGameSessionProtectionPolicy' = Maybe ProtectionPolicy
a} :: FleetAttributes)

-- | The operating system of the fleet\'s computing resources. A fleet\'s
-- operating system is determined by the OS of the build or script that is
-- deployed on this fleet.
fleetAttributes_operatingSystem :: Lens.Lens' FleetAttributes (Prelude.Maybe OperatingSystem)
fleetAttributes_operatingSystem :: Lens' FleetAttributes (Maybe OperatingSystem)
fleetAttributes_operatingSystem = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe OperatingSystem
operatingSystem :: Maybe OperatingSystem
$sel:operatingSystem:FleetAttributes' :: FleetAttributes -> Maybe OperatingSystem
operatingSystem} -> Maybe OperatingSystem
operatingSystem) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe OperatingSystem
a -> FleetAttributes
s {$sel:operatingSystem:FleetAttributes' :: Maybe OperatingSystem
operatingSystem = Maybe OperatingSystem
a} :: FleetAttributes)

-- | Undocumented member.
fleetAttributes_resourceCreationLimitPolicy :: Lens.Lens' FleetAttributes (Prelude.Maybe ResourceCreationLimitPolicy)
fleetAttributes_resourceCreationLimitPolicy :: Lens' FleetAttributes (Maybe ResourceCreationLimitPolicy)
fleetAttributes_resourceCreationLimitPolicy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe ResourceCreationLimitPolicy
resourceCreationLimitPolicy :: Maybe ResourceCreationLimitPolicy
$sel:resourceCreationLimitPolicy:FleetAttributes' :: FleetAttributes -> Maybe ResourceCreationLimitPolicy
resourceCreationLimitPolicy} -> Maybe ResourceCreationLimitPolicy
resourceCreationLimitPolicy) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe ResourceCreationLimitPolicy
a -> FleetAttributes
s {$sel:resourceCreationLimitPolicy:FleetAttributes' :: Maybe ResourceCreationLimitPolicy
resourceCreationLimitPolicy = Maybe ResourceCreationLimitPolicy
a} :: FleetAttributes)

-- | The Amazon Resource Name
-- (<https://docs.aws.amazon.com/AmazonS3/latest/dev/s3-arn-format.html ARN>)
-- associated with the GameLift script resource that is deployed on
-- instances in this fleet. In a GameLift script ARN, the resource ID
-- matches the @ScriptId@ value.
fleetAttributes_scriptArn :: Lens.Lens' FleetAttributes (Prelude.Maybe Prelude.Text)
fleetAttributes_scriptArn :: Lens' FleetAttributes (Maybe Text)
fleetAttributes_scriptArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe Text
scriptArn :: Maybe Text
$sel:scriptArn:FleetAttributes' :: FleetAttributes -> Maybe Text
scriptArn} -> Maybe Text
scriptArn) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe Text
a -> FleetAttributes
s {$sel:scriptArn:FleetAttributes' :: Maybe Text
scriptArn = Maybe Text
a} :: FleetAttributes)

-- | A unique identifier for the Realtime script resource that is deployed on
-- instances in this fleet.
fleetAttributes_scriptId :: Lens.Lens' FleetAttributes (Prelude.Maybe Prelude.Text)
fleetAttributes_scriptId :: Lens' FleetAttributes (Maybe Text)
fleetAttributes_scriptId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe Text
scriptId :: Maybe Text
$sel:scriptId:FleetAttributes' :: FleetAttributes -> Maybe Text
scriptId} -> Maybe Text
scriptId) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe Text
a -> FleetAttributes
s {$sel:scriptId:FleetAttributes' :: Maybe Text
scriptId = Maybe Text
a} :: FleetAttributes)

-- | __This parameter is no longer used.__ Server launch parameters are now
-- defined using the fleet\'s runtime configuration . Requests that use
-- this parameter instead continue to be valid.
fleetAttributes_serverLaunchParameters :: Lens.Lens' FleetAttributes (Prelude.Maybe Prelude.Text)
fleetAttributes_serverLaunchParameters :: Lens' FleetAttributes (Maybe Text)
fleetAttributes_serverLaunchParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe Text
serverLaunchParameters :: Maybe Text
$sel:serverLaunchParameters:FleetAttributes' :: FleetAttributes -> Maybe Text
serverLaunchParameters} -> Maybe Text
serverLaunchParameters) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe Text
a -> FleetAttributes
s {$sel:serverLaunchParameters:FleetAttributes' :: Maybe Text
serverLaunchParameters = Maybe Text
a} :: FleetAttributes)

-- | __This parameter is no longer used.__ Server launch paths are now
-- defined using the fleet\'s
-- <https://docs.aws.amazon.com/gamelift/latest/apireference/RuntimeConfiguration.html RuntimeConfiguration>
-- . Requests that use this parameter instead continue to be valid.
fleetAttributes_serverLaunchPath :: Lens.Lens' FleetAttributes (Prelude.Maybe Prelude.Text)
fleetAttributes_serverLaunchPath :: Lens' FleetAttributes (Maybe Text)
fleetAttributes_serverLaunchPath = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe Text
serverLaunchPath :: Maybe Text
$sel:serverLaunchPath:FleetAttributes' :: FleetAttributes -> Maybe Text
serverLaunchPath} -> Maybe Text
serverLaunchPath) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe Text
a -> FleetAttributes
s {$sel:serverLaunchPath:FleetAttributes' :: Maybe Text
serverLaunchPath = Maybe Text
a} :: FleetAttributes)

-- | Current status of the fleet. Possible fleet statuses include the
-- following:
--
-- -   __NEW__ -- A new fleet has been defined and desired instances is set
--     to 1.
--
-- -   __DOWNLOADING\/VALIDATING\/BUILDING\/ACTIVATING__ -- GameLift is
--     setting up the new fleet, creating new instances with the game build
--     or Realtime script and starting server processes.
--
-- -   __ACTIVE__ -- Hosts can now accept game sessions.
--
-- -   __ERROR__ -- An error occurred when downloading, validating,
--     building, or activating the fleet.
--
-- -   __DELETING__ -- Hosts are responding to a delete fleet request.
--
-- -   __TERMINATED__ -- The fleet no longer exists.
fleetAttributes_status :: Lens.Lens' FleetAttributes (Prelude.Maybe FleetStatus)
fleetAttributes_status :: Lens' FleetAttributes (Maybe FleetStatus)
fleetAttributes_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe FleetStatus
status :: Maybe FleetStatus
$sel:status:FleetAttributes' :: FleetAttributes -> Maybe FleetStatus
status} -> Maybe FleetStatus
status) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe FleetStatus
a -> FleetAttributes
s {$sel:status:FleetAttributes' :: Maybe FleetStatus
status = Maybe FleetStatus
a} :: FleetAttributes)

-- | A list of fleet activity that has been suspended using
-- <https://docs.aws.amazon.com/gamelift/latest/apireference/API_StopFleetActions.html StopFleetActions>
-- . This includes fleet auto-scaling.
fleetAttributes_stoppedActions :: Lens.Lens' FleetAttributes (Prelude.Maybe (Prelude.NonEmpty FleetAction))
fleetAttributes_stoppedActions :: Lens' FleetAttributes (Maybe (NonEmpty FleetAction))
fleetAttributes_stoppedActions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe (NonEmpty FleetAction)
stoppedActions :: Maybe (NonEmpty FleetAction)
$sel:stoppedActions:FleetAttributes' :: FleetAttributes -> Maybe (NonEmpty FleetAction)
stoppedActions} -> Maybe (NonEmpty FleetAction)
stoppedActions) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe (NonEmpty FleetAction)
a -> FleetAttributes
s {$sel:stoppedActions:FleetAttributes' :: Maybe (NonEmpty FleetAction)
stoppedActions = Maybe (NonEmpty FleetAction)
a} :: FleetAttributes) 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

-- | A time stamp indicating when this data object was terminated. Format is
-- a number expressed in Unix time as milliseconds (for example
-- @\"1469498468.057\"@).
fleetAttributes_terminationTime :: Lens.Lens' FleetAttributes (Prelude.Maybe Prelude.UTCTime)
fleetAttributes_terminationTime :: Lens' FleetAttributes (Maybe UTCTime)
fleetAttributes_terminationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetAttributes' {Maybe POSIX
terminationTime :: Maybe POSIX
$sel:terminationTime:FleetAttributes' :: FleetAttributes -> Maybe POSIX
terminationTime} -> Maybe POSIX
terminationTime) (\s :: FleetAttributes
s@FleetAttributes' {} Maybe POSIX
a -> FleetAttributes
s {$sel:terminationTime:FleetAttributes' :: Maybe POSIX
terminationTime = Maybe POSIX
a} :: FleetAttributes) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Data.FromJSON FleetAttributes where
  parseJSON :: Value -> Parser FleetAttributes
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"FleetAttributes"
      ( \Object
x ->
          Maybe AnywhereConfiguration
-> Maybe Text
-> Maybe Text
-> Maybe CertificateConfiguration
-> Maybe ComputeType
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe FleetType
-> Maybe Text
-> Maybe EC2InstanceType
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Text
-> Maybe ProtectionPolicy
-> Maybe OperatingSystem
-> Maybe ResourceCreationLimitPolicy
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe FleetStatus
-> Maybe (NonEmpty FleetAction)
-> Maybe POSIX
-> FleetAttributes
FleetAttributes'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"AnywhereConfiguration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"BuildArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"BuildId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"CertificateConfiguration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ComputeType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"CreationTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Description")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"FleetArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"FleetId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"FleetType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"InstanceRoleArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"InstanceType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"LogPaths" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"MetricGroups" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Name")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"NewGameSessionProtectionPolicy")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"OperatingSystem")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ResourceCreationLimitPolicy")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ScriptArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ScriptId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ServerLaunchParameters")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ServerLaunchPath")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Status")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"StoppedActions")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"TerminationTime")
      )

instance Prelude.Hashable FleetAttributes where
  hashWithSalt :: Int -> FleetAttributes -> Int
hashWithSalt Int
_salt FleetAttributes' {Maybe [Text]
Maybe (NonEmpty FleetAction)
Maybe Text
Maybe POSIX
Maybe AnywhereConfiguration
Maybe CertificateConfiguration
Maybe ComputeType
Maybe EC2InstanceType
Maybe FleetStatus
Maybe FleetType
Maybe OperatingSystem
Maybe ProtectionPolicy
Maybe ResourceCreationLimitPolicy
terminationTime :: Maybe POSIX
stoppedActions :: Maybe (NonEmpty FleetAction)
status :: Maybe FleetStatus
serverLaunchPath :: Maybe Text
serverLaunchParameters :: Maybe Text
scriptId :: Maybe Text
scriptArn :: Maybe Text
resourceCreationLimitPolicy :: Maybe ResourceCreationLimitPolicy
operatingSystem :: Maybe OperatingSystem
newGameSessionProtectionPolicy' :: Maybe ProtectionPolicy
name :: Maybe Text
metricGroups :: Maybe [Text]
logPaths :: Maybe [Text]
instanceType :: Maybe EC2InstanceType
instanceRoleArn :: Maybe Text
fleetType :: Maybe FleetType
fleetId :: Maybe Text
fleetArn :: Maybe Text
description :: Maybe Text
creationTime :: Maybe POSIX
computeType :: Maybe ComputeType
certificateConfiguration :: Maybe CertificateConfiguration
buildId :: Maybe Text
buildArn :: Maybe Text
anywhereConfiguration :: Maybe AnywhereConfiguration
$sel:terminationTime:FleetAttributes' :: FleetAttributes -> Maybe POSIX
$sel:stoppedActions:FleetAttributes' :: FleetAttributes -> Maybe (NonEmpty FleetAction)
$sel:status:FleetAttributes' :: FleetAttributes -> Maybe FleetStatus
$sel:serverLaunchPath:FleetAttributes' :: FleetAttributes -> Maybe Text
$sel:serverLaunchParameters:FleetAttributes' :: FleetAttributes -> Maybe Text
$sel:scriptId:FleetAttributes' :: FleetAttributes -> Maybe Text
$sel:scriptArn:FleetAttributes' :: FleetAttributes -> Maybe Text
$sel:resourceCreationLimitPolicy:FleetAttributes' :: FleetAttributes -> Maybe ResourceCreationLimitPolicy
$sel:operatingSystem:FleetAttributes' :: FleetAttributes -> Maybe OperatingSystem
$sel:newGameSessionProtectionPolicy':FleetAttributes' :: FleetAttributes -> Maybe ProtectionPolicy
$sel:name:FleetAttributes' :: FleetAttributes -> Maybe Text
$sel:metricGroups:FleetAttributes' :: FleetAttributes -> Maybe [Text]
$sel:logPaths:FleetAttributes' :: FleetAttributes -> Maybe [Text]
$sel:instanceType:FleetAttributes' :: FleetAttributes -> Maybe EC2InstanceType
$sel:instanceRoleArn:FleetAttributes' :: FleetAttributes -> Maybe Text
$sel:fleetType:FleetAttributes' :: FleetAttributes -> Maybe FleetType
$sel:fleetId:FleetAttributes' :: FleetAttributes -> Maybe Text
$sel:fleetArn:FleetAttributes' :: FleetAttributes -> Maybe Text
$sel:description:FleetAttributes' :: FleetAttributes -> Maybe Text
$sel:creationTime:FleetAttributes' :: FleetAttributes -> Maybe POSIX
$sel:computeType:FleetAttributes' :: FleetAttributes -> Maybe ComputeType
$sel:certificateConfiguration:FleetAttributes' :: FleetAttributes -> Maybe CertificateConfiguration
$sel:buildId:FleetAttributes' :: FleetAttributes -> Maybe Text
$sel:buildArn:FleetAttributes' :: FleetAttributes -> Maybe Text
$sel:anywhereConfiguration:FleetAttributes' :: FleetAttributes -> Maybe AnywhereConfiguration
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnywhereConfiguration
anywhereConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
buildArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
buildId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CertificateConfiguration
certificateConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ComputeType
computeType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
creationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
fleetArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
fleetId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FleetType
fleetType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
instanceRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EC2InstanceType
instanceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
logPaths
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
metricGroups
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ProtectionPolicy
newGameSessionProtectionPolicy'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OperatingSystem
operatingSystem
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ResourceCreationLimitPolicy
resourceCreationLimitPolicy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
scriptArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
scriptId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
serverLaunchParameters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
serverLaunchPath
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FleetStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty FleetAction)
stoppedActions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
terminationTime

instance Prelude.NFData FleetAttributes where
  rnf :: FleetAttributes -> ()
rnf FleetAttributes' {Maybe [Text]
Maybe (NonEmpty FleetAction)
Maybe Text
Maybe POSIX
Maybe AnywhereConfiguration
Maybe CertificateConfiguration
Maybe ComputeType
Maybe EC2InstanceType
Maybe FleetStatus
Maybe FleetType
Maybe OperatingSystem
Maybe ProtectionPolicy
Maybe ResourceCreationLimitPolicy
terminationTime :: Maybe POSIX
stoppedActions :: Maybe (NonEmpty FleetAction)
status :: Maybe FleetStatus
serverLaunchPath :: Maybe Text
serverLaunchParameters :: Maybe Text
scriptId :: Maybe Text
scriptArn :: Maybe Text
resourceCreationLimitPolicy :: Maybe ResourceCreationLimitPolicy
operatingSystem :: Maybe OperatingSystem
newGameSessionProtectionPolicy' :: Maybe ProtectionPolicy
name :: Maybe Text
metricGroups :: Maybe [Text]
logPaths :: Maybe [Text]
instanceType :: Maybe EC2InstanceType
instanceRoleArn :: Maybe Text
fleetType :: Maybe FleetType
fleetId :: Maybe Text
fleetArn :: Maybe Text
description :: Maybe Text
creationTime :: Maybe POSIX
computeType :: Maybe ComputeType
certificateConfiguration :: Maybe CertificateConfiguration
buildId :: Maybe Text
buildArn :: Maybe Text
anywhereConfiguration :: Maybe AnywhereConfiguration
$sel:terminationTime:FleetAttributes' :: FleetAttributes -> Maybe POSIX
$sel:stoppedActions:FleetAttributes' :: FleetAttributes -> Maybe (NonEmpty FleetAction)
$sel:status:FleetAttributes' :: FleetAttributes -> Maybe FleetStatus
$sel:serverLaunchPath:FleetAttributes' :: FleetAttributes -> Maybe Text
$sel:serverLaunchParameters:FleetAttributes' :: FleetAttributes -> Maybe Text
$sel:scriptId:FleetAttributes' :: FleetAttributes -> Maybe Text
$sel:scriptArn:FleetAttributes' :: FleetAttributes -> Maybe Text
$sel:resourceCreationLimitPolicy:FleetAttributes' :: FleetAttributes -> Maybe ResourceCreationLimitPolicy
$sel:operatingSystem:FleetAttributes' :: FleetAttributes -> Maybe OperatingSystem
$sel:newGameSessionProtectionPolicy':FleetAttributes' :: FleetAttributes -> Maybe ProtectionPolicy
$sel:name:FleetAttributes' :: FleetAttributes -> Maybe Text
$sel:metricGroups:FleetAttributes' :: FleetAttributes -> Maybe [Text]
$sel:logPaths:FleetAttributes' :: FleetAttributes -> Maybe [Text]
$sel:instanceType:FleetAttributes' :: FleetAttributes -> Maybe EC2InstanceType
$sel:instanceRoleArn:FleetAttributes' :: FleetAttributes -> Maybe Text
$sel:fleetType:FleetAttributes' :: FleetAttributes -> Maybe FleetType
$sel:fleetId:FleetAttributes' :: FleetAttributes -> Maybe Text
$sel:fleetArn:FleetAttributes' :: FleetAttributes -> Maybe Text
$sel:description:FleetAttributes' :: FleetAttributes -> Maybe Text
$sel:creationTime:FleetAttributes' :: FleetAttributes -> Maybe POSIX
$sel:computeType:FleetAttributes' :: FleetAttributes -> Maybe ComputeType
$sel:certificateConfiguration:FleetAttributes' :: FleetAttributes -> Maybe CertificateConfiguration
$sel:buildId:FleetAttributes' :: FleetAttributes -> Maybe Text
$sel:buildArn:FleetAttributes' :: FleetAttributes -> Maybe Text
$sel:anywhereConfiguration:FleetAttributes' :: FleetAttributes -> Maybe AnywhereConfiguration
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AnywhereConfiguration
anywhereConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
buildArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
buildId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CertificateConfiguration
certificateConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ComputeType
computeType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
fleetArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
fleetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FleetType
fleetType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
instanceRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EC2InstanceType
instanceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
logPaths
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
metricGroups
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe ProtectionPolicy
newGameSessionProtectionPolicy'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OperatingSystem
operatingSystem
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe ResourceCreationLimitPolicy
resourceCreationLimitPolicy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
scriptArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
scriptId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
serverLaunchParameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
serverLaunchPath
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FleetStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe (NonEmpty FleetAction)
stoppedActions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe POSIX
terminationTime