{-# 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.FleetCapacity
-- 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.FleetCapacity 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.EC2InstanceCounts
import Amazonka.GameLift.Types.EC2InstanceType
import qualified Amazonka.Prelude as Prelude

-- | Current resource capacity settings in a specified fleet or location. The
-- location value might refer to a fleet\'s remote location or its home
-- Region.
--
-- __Related actions__
--
-- <https://docs.aws.amazon.com/gamelift/latest/apireference/API_DescribeFleetCapacity.html DescribeFleetCapacity>
-- |
-- <https://docs.aws.amazon.com/gamelift/latest/apireference/API_DescribeFleetLocationCapacity.html DescribeFleetLocationCapacity>
-- |
-- <https://docs.aws.amazon.com/gamelift/latest/apireference/API_UpdateFleetCapacity.html UpdateFleetCapacity>
--
-- /See:/ 'newFleetCapacity' smart constructor.
data FleetCapacity = FleetCapacity'
  { -- | 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@.
    FleetCapacity -> Maybe Text
fleetArn :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the fleet associated with the location.
    FleetCapacity -> Maybe Text
fleetId :: Prelude.Maybe Prelude.Text,
    FleetCapacity -> Maybe EC2InstanceCounts
instanceCounts :: Prelude.Maybe EC2InstanceCounts,
    -- | The Amazon EC2 instance type that is used for all instances in a fleet.
    -- The instance type determines the computing resources in use, including
    -- CPU, memory, storage, and networking capacity. See
    -- <http://aws.amazon.com/ec2/instance-types/ Amazon Elastic Compute Cloud Instance Types>
    -- for detailed descriptions.
    FleetCapacity -> Maybe EC2InstanceType
instanceType :: Prelude.Maybe EC2InstanceType,
    -- | The fleet location for the instance count information, expressed as an
    -- Amazon Web Services Region code, such as @us-west-2@.
    FleetCapacity -> Maybe Text
location :: Prelude.Maybe Prelude.Text
  }
  deriving (FleetCapacity -> FleetCapacity -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FleetCapacity -> FleetCapacity -> Bool
$c/= :: FleetCapacity -> FleetCapacity -> Bool
== :: FleetCapacity -> FleetCapacity -> Bool
$c== :: FleetCapacity -> FleetCapacity -> Bool
Prelude.Eq, ReadPrec [FleetCapacity]
ReadPrec FleetCapacity
Int -> ReadS FleetCapacity
ReadS [FleetCapacity]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FleetCapacity]
$creadListPrec :: ReadPrec [FleetCapacity]
readPrec :: ReadPrec FleetCapacity
$creadPrec :: ReadPrec FleetCapacity
readList :: ReadS [FleetCapacity]
$creadList :: ReadS [FleetCapacity]
readsPrec :: Int -> ReadS FleetCapacity
$creadsPrec :: Int -> ReadS FleetCapacity
Prelude.Read, Int -> FleetCapacity -> ShowS
[FleetCapacity] -> ShowS
FleetCapacity -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FleetCapacity] -> ShowS
$cshowList :: [FleetCapacity] -> ShowS
show :: FleetCapacity -> String
$cshow :: FleetCapacity -> String
showsPrec :: Int -> FleetCapacity -> ShowS
$cshowsPrec :: Int -> FleetCapacity -> ShowS
Prelude.Show, forall x. Rep FleetCapacity x -> FleetCapacity
forall x. FleetCapacity -> Rep FleetCapacity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FleetCapacity x -> FleetCapacity
$cfrom :: forall x. FleetCapacity -> Rep FleetCapacity x
Prelude.Generic)

-- |
-- Create a value of 'FleetCapacity' 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:
--
-- 'fleetArn', 'fleetCapacity_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@.
--
-- 'fleetId', 'fleetCapacity_fleetId' - A unique identifier for the fleet associated with the location.
--
-- 'instanceCounts', 'fleetCapacity_instanceCounts' - Undocumented member.
--
-- 'instanceType', 'fleetCapacity_instanceType' - The Amazon EC2 instance type that is used for all instances in a fleet.
-- The instance type determines the computing resources in use, including
-- CPU, memory, storage, and networking capacity. See
-- <http://aws.amazon.com/ec2/instance-types/ Amazon Elastic Compute Cloud Instance Types>
-- for detailed descriptions.
--
-- 'location', 'fleetCapacity_location' - The fleet location for the instance count information, expressed as an
-- Amazon Web Services Region code, such as @us-west-2@.
newFleetCapacity ::
  FleetCapacity
newFleetCapacity :: FleetCapacity
newFleetCapacity =
  FleetCapacity'
    { $sel:fleetArn:FleetCapacity' :: Maybe Text
fleetArn = forall a. Maybe a
Prelude.Nothing,
      $sel:fleetId:FleetCapacity' :: Maybe Text
fleetId = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceCounts:FleetCapacity' :: Maybe EC2InstanceCounts
instanceCounts = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceType:FleetCapacity' :: Maybe EC2InstanceType
instanceType = forall a. Maybe a
Prelude.Nothing,
      $sel:location:FleetCapacity' :: Maybe Text
location = forall a. Maybe a
Prelude.Nothing
    }

-- | 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@.
fleetCapacity_fleetArn :: Lens.Lens' FleetCapacity (Prelude.Maybe Prelude.Text)
fleetCapacity_fleetArn :: Lens' FleetCapacity (Maybe Text)
fleetCapacity_fleetArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetCapacity' {Maybe Text
fleetArn :: Maybe Text
$sel:fleetArn:FleetCapacity' :: FleetCapacity -> Maybe Text
fleetArn} -> Maybe Text
fleetArn) (\s :: FleetCapacity
s@FleetCapacity' {} Maybe Text
a -> FleetCapacity
s {$sel:fleetArn:FleetCapacity' :: Maybe Text
fleetArn = Maybe Text
a} :: FleetCapacity)

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

-- | Undocumented member.
fleetCapacity_instanceCounts :: Lens.Lens' FleetCapacity (Prelude.Maybe EC2InstanceCounts)
fleetCapacity_instanceCounts :: Lens' FleetCapacity (Maybe EC2InstanceCounts)
fleetCapacity_instanceCounts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetCapacity' {Maybe EC2InstanceCounts
instanceCounts :: Maybe EC2InstanceCounts
$sel:instanceCounts:FleetCapacity' :: FleetCapacity -> Maybe EC2InstanceCounts
instanceCounts} -> Maybe EC2InstanceCounts
instanceCounts) (\s :: FleetCapacity
s@FleetCapacity' {} Maybe EC2InstanceCounts
a -> FleetCapacity
s {$sel:instanceCounts:FleetCapacity' :: Maybe EC2InstanceCounts
instanceCounts = Maybe EC2InstanceCounts
a} :: FleetCapacity)

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

-- | The fleet location for the instance count information, expressed as an
-- Amazon Web Services Region code, such as @us-west-2@.
fleetCapacity_location :: Lens.Lens' FleetCapacity (Prelude.Maybe Prelude.Text)
fleetCapacity_location :: Lens' FleetCapacity (Maybe Text)
fleetCapacity_location = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FleetCapacity' {Maybe Text
location :: Maybe Text
$sel:location:FleetCapacity' :: FleetCapacity -> Maybe Text
location} -> Maybe Text
location) (\s :: FleetCapacity
s@FleetCapacity' {} Maybe Text
a -> FleetCapacity
s {$sel:location:FleetCapacity' :: Maybe Text
location = Maybe Text
a} :: FleetCapacity)

instance Data.FromJSON FleetCapacity where
  parseJSON :: Value -> Parser FleetCapacity
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"FleetCapacity"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe EC2InstanceCounts
-> Maybe EC2InstanceType
-> Maybe Text
-> FleetCapacity
FleetCapacity'
            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
"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
"InstanceCounts")
            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
"Location")
      )

instance Prelude.Hashable FleetCapacity where
  hashWithSalt :: Int -> FleetCapacity -> Int
hashWithSalt Int
_salt FleetCapacity' {Maybe Text
Maybe EC2InstanceCounts
Maybe EC2InstanceType
location :: Maybe Text
instanceType :: Maybe EC2InstanceType
instanceCounts :: Maybe EC2InstanceCounts
fleetId :: Maybe Text
fleetArn :: Maybe Text
$sel:location:FleetCapacity' :: FleetCapacity -> Maybe Text
$sel:instanceType:FleetCapacity' :: FleetCapacity -> Maybe EC2InstanceType
$sel:instanceCounts:FleetCapacity' :: FleetCapacity -> Maybe EC2InstanceCounts
$sel:fleetId:FleetCapacity' :: FleetCapacity -> Maybe Text
$sel:fleetArn:FleetCapacity' :: FleetCapacity -> Maybe Text
..} =
    Int
_salt
      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 EC2InstanceCounts
instanceCounts
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EC2InstanceType
instanceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
location

instance Prelude.NFData FleetCapacity where
  rnf :: FleetCapacity -> ()
rnf FleetCapacity' {Maybe Text
Maybe EC2InstanceCounts
Maybe EC2InstanceType
location :: Maybe Text
instanceType :: Maybe EC2InstanceType
instanceCounts :: Maybe EC2InstanceCounts
fleetId :: Maybe Text
fleetArn :: Maybe Text
$sel:location:FleetCapacity' :: FleetCapacity -> Maybe Text
$sel:instanceType:FleetCapacity' :: FleetCapacity -> Maybe EC2InstanceType
$sel:instanceCounts:FleetCapacity' :: FleetCapacity -> Maybe EC2InstanceCounts
$sel:fleetId:FleetCapacity' :: FleetCapacity -> Maybe Text
$sel:fleetArn:FleetCapacity' :: FleetCapacity -> Maybe Text
..} =
    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 EC2InstanceCounts
instanceCounts
      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
location