{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# 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.DescribeFleetLocationAttributes
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves information on a fleet\'s remote locations, including
-- life-cycle status and any suspended fleet activity.
--
-- This operation can be used in the following ways:
--
-- -   To get data for specific locations, provide a fleet identifier and a
--     list of locations. Location data is returned in the order that it is
--     requested.
--
-- -   To get data for all locations, provide a fleet identifier only.
--     Location data is returned in no particular order.
--
-- When requesting attributes for multiple locations, use the pagination
-- parameters to retrieve results as a set of sequential pages.
--
-- If successful, a @LocationAttributes@ object is returned for each
-- requested location. If the fleet does not have a requested location, no
-- information is returned. This operation does not return the home Region.
-- To get information on a fleet\'s home Region, call
-- @DescribeFleetAttributes@.
--
-- __Learn more__
--
-- <https://docs.aws.amazon.com/gamelift/latest/developerguide/fleets-intro.html Setting up GameLift fleets>
module Amazonka.GameLift.DescribeFleetLocationAttributes
  ( -- * Creating a Request
    DescribeFleetLocationAttributes (..),
    newDescribeFleetLocationAttributes,

    -- * Request Lenses
    describeFleetLocationAttributes_limit,
    describeFleetLocationAttributes_locations,
    describeFleetLocationAttributes_nextToken,
    describeFleetLocationAttributes_fleetId,

    -- * Destructuring the Response
    DescribeFleetLocationAttributesResponse (..),
    newDescribeFleetLocationAttributesResponse,

    -- * Response Lenses
    describeFleetLocationAttributesResponse_fleetArn,
    describeFleetLocationAttributesResponse_fleetId,
    describeFleetLocationAttributesResponse_locationAttributes,
    describeFleetLocationAttributesResponse_nextToken,
    describeFleetLocationAttributesResponse_httpStatus,
  )
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
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDescribeFleetLocationAttributes' smart constructor.
data DescribeFleetLocationAttributes = DescribeFleetLocationAttributes'
  { -- | The maximum number of results to return. Use this parameter with
    -- @NextToken@ to get results as a set of sequential pages. This limit is
    -- not currently enforced.
    DescribeFleetLocationAttributes -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
    -- | A list of fleet locations to retrieve information for. Specify locations
    -- in the form of an Amazon Web Services Region code, such as @us-west-2@.
    DescribeFleetLocationAttributes -> Maybe (NonEmpty Text)
locations :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | A token that indicates the start of the next sequential page of results.
    -- Use the token that is returned with a previous call to this operation.
    -- To start at the beginning of the result set, do not specify a value.
    DescribeFleetLocationAttributes -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the fleet to retrieve remote locations for. You
    -- can use either the fleet ID or ARN value.
    DescribeFleetLocationAttributes -> Text
fleetId :: Prelude.Text
  }
  deriving (DescribeFleetLocationAttributes
-> DescribeFleetLocationAttributes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeFleetLocationAttributes
-> DescribeFleetLocationAttributes -> Bool
$c/= :: DescribeFleetLocationAttributes
-> DescribeFleetLocationAttributes -> Bool
== :: DescribeFleetLocationAttributes
-> DescribeFleetLocationAttributes -> Bool
$c== :: DescribeFleetLocationAttributes
-> DescribeFleetLocationAttributes -> Bool
Prelude.Eq, ReadPrec [DescribeFleetLocationAttributes]
ReadPrec DescribeFleetLocationAttributes
Int -> ReadS DescribeFleetLocationAttributes
ReadS [DescribeFleetLocationAttributes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeFleetLocationAttributes]
$creadListPrec :: ReadPrec [DescribeFleetLocationAttributes]
readPrec :: ReadPrec DescribeFleetLocationAttributes
$creadPrec :: ReadPrec DescribeFleetLocationAttributes
readList :: ReadS [DescribeFleetLocationAttributes]
$creadList :: ReadS [DescribeFleetLocationAttributes]
readsPrec :: Int -> ReadS DescribeFleetLocationAttributes
$creadsPrec :: Int -> ReadS DescribeFleetLocationAttributes
Prelude.Read, Int -> DescribeFleetLocationAttributes -> ShowS
[DescribeFleetLocationAttributes] -> ShowS
DescribeFleetLocationAttributes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeFleetLocationAttributes] -> ShowS
$cshowList :: [DescribeFleetLocationAttributes] -> ShowS
show :: DescribeFleetLocationAttributes -> String
$cshow :: DescribeFleetLocationAttributes -> String
showsPrec :: Int -> DescribeFleetLocationAttributes -> ShowS
$cshowsPrec :: Int -> DescribeFleetLocationAttributes -> ShowS
Prelude.Show, forall x.
Rep DescribeFleetLocationAttributes x
-> DescribeFleetLocationAttributes
forall x.
DescribeFleetLocationAttributes
-> Rep DescribeFleetLocationAttributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeFleetLocationAttributes x
-> DescribeFleetLocationAttributes
$cfrom :: forall x.
DescribeFleetLocationAttributes
-> Rep DescribeFleetLocationAttributes x
Prelude.Generic)

-- |
-- Create a value of 'DescribeFleetLocationAttributes' 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:
--
-- 'limit', 'describeFleetLocationAttributes_limit' - The maximum number of results to return. Use this parameter with
-- @NextToken@ to get results as a set of sequential pages. This limit is
-- not currently enforced.
--
-- 'locations', 'describeFleetLocationAttributes_locations' - A list of fleet locations to retrieve information for. Specify locations
-- in the form of an Amazon Web Services Region code, such as @us-west-2@.
--
-- 'nextToken', 'describeFleetLocationAttributes_nextToken' - A token that indicates the start of the next sequential page of results.
-- Use the token that is returned with a previous call to this operation.
-- To start at the beginning of the result set, do not specify a value.
--
-- 'fleetId', 'describeFleetLocationAttributes_fleetId' - A unique identifier for the fleet to retrieve remote locations for. You
-- can use either the fleet ID or ARN value.
newDescribeFleetLocationAttributes ::
  -- | 'fleetId'
  Prelude.Text ->
  DescribeFleetLocationAttributes
newDescribeFleetLocationAttributes :: Text -> DescribeFleetLocationAttributes
newDescribeFleetLocationAttributes Text
pFleetId_ =
  DescribeFleetLocationAttributes'
    { $sel:limit:DescribeFleetLocationAttributes' :: Maybe Natural
limit =
        forall a. Maybe a
Prelude.Nothing,
      $sel:locations:DescribeFleetLocationAttributes' :: Maybe (NonEmpty Text)
locations = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeFleetLocationAttributes' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:fleetId:DescribeFleetLocationAttributes' :: Text
fleetId = Text
pFleetId_
    }

-- | The maximum number of results to return. Use this parameter with
-- @NextToken@ to get results as a set of sequential pages. This limit is
-- not currently enforced.
describeFleetLocationAttributes_limit :: Lens.Lens' DescribeFleetLocationAttributes (Prelude.Maybe Prelude.Natural)
describeFleetLocationAttributes_limit :: Lens' DescribeFleetLocationAttributes (Maybe Natural)
describeFleetLocationAttributes_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFleetLocationAttributes' {Maybe Natural
limit :: Maybe Natural
$sel:limit:DescribeFleetLocationAttributes' :: DescribeFleetLocationAttributes -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: DescribeFleetLocationAttributes
s@DescribeFleetLocationAttributes' {} Maybe Natural
a -> DescribeFleetLocationAttributes
s {$sel:limit:DescribeFleetLocationAttributes' :: Maybe Natural
limit = Maybe Natural
a} :: DescribeFleetLocationAttributes)

-- | A list of fleet locations to retrieve information for. Specify locations
-- in the form of an Amazon Web Services Region code, such as @us-west-2@.
describeFleetLocationAttributes_locations :: Lens.Lens' DescribeFleetLocationAttributes (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
describeFleetLocationAttributes_locations :: Lens' DescribeFleetLocationAttributes (Maybe (NonEmpty Text))
describeFleetLocationAttributes_locations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFleetLocationAttributes' {Maybe (NonEmpty Text)
locations :: Maybe (NonEmpty Text)
$sel:locations:DescribeFleetLocationAttributes' :: DescribeFleetLocationAttributes -> Maybe (NonEmpty Text)
locations} -> Maybe (NonEmpty Text)
locations) (\s :: DescribeFleetLocationAttributes
s@DescribeFleetLocationAttributes' {} Maybe (NonEmpty Text)
a -> DescribeFleetLocationAttributes
s {$sel:locations:DescribeFleetLocationAttributes' :: Maybe (NonEmpty Text)
locations = Maybe (NonEmpty Text)
a} :: DescribeFleetLocationAttributes) 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 token that indicates the start of the next sequential page of results.
-- Use the token that is returned with a previous call to this operation.
-- To start at the beginning of the result set, do not specify a value.
describeFleetLocationAttributes_nextToken :: Lens.Lens' DescribeFleetLocationAttributes (Prelude.Maybe Prelude.Text)
describeFleetLocationAttributes_nextToken :: Lens' DescribeFleetLocationAttributes (Maybe Text)
describeFleetLocationAttributes_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFleetLocationAttributes' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeFleetLocationAttributes' :: DescribeFleetLocationAttributes -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeFleetLocationAttributes
s@DescribeFleetLocationAttributes' {} Maybe Text
a -> DescribeFleetLocationAttributes
s {$sel:nextToken:DescribeFleetLocationAttributes' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeFleetLocationAttributes)

-- | A unique identifier for the fleet to retrieve remote locations for. You
-- can use either the fleet ID or ARN value.
describeFleetLocationAttributes_fleetId :: Lens.Lens' DescribeFleetLocationAttributes Prelude.Text
describeFleetLocationAttributes_fleetId :: Lens' DescribeFleetLocationAttributes Text
describeFleetLocationAttributes_fleetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFleetLocationAttributes' {Text
fleetId :: Text
$sel:fleetId:DescribeFleetLocationAttributes' :: DescribeFleetLocationAttributes -> Text
fleetId} -> Text
fleetId) (\s :: DescribeFleetLocationAttributes
s@DescribeFleetLocationAttributes' {} Text
a -> DescribeFleetLocationAttributes
s {$sel:fleetId:DescribeFleetLocationAttributes' :: Text
fleetId = Text
a} :: DescribeFleetLocationAttributes)

instance
  Core.AWSRequest
    DescribeFleetLocationAttributes
  where
  type
    AWSResponse DescribeFleetLocationAttributes =
      DescribeFleetLocationAttributesResponse
  request :: (Service -> Service)
-> DescribeFleetLocationAttributes
-> Request DescribeFleetLocationAttributes
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeFleetLocationAttributes
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse DescribeFleetLocationAttributes)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe [LocationAttributes]
-> Maybe Text
-> Int
-> DescribeFleetLocationAttributesResponse
DescribeFleetLocationAttributesResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (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 -> Either String (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 -> Either String (Maybe a)
Data..?> Key
"LocationAttributes"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ 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 -> Either String (Maybe a)
Data..?> Key
"NextToken")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance
  Prelude.Hashable
    DescribeFleetLocationAttributes
  where
  hashWithSalt :: Int -> DescribeFleetLocationAttributes -> Int
hashWithSalt
    Int
_salt
    DescribeFleetLocationAttributes' {Maybe Natural
Maybe (NonEmpty Text)
Maybe Text
Text
fleetId :: Text
nextToken :: Maybe Text
locations :: Maybe (NonEmpty Text)
limit :: Maybe Natural
$sel:fleetId:DescribeFleetLocationAttributes' :: DescribeFleetLocationAttributes -> Text
$sel:nextToken:DescribeFleetLocationAttributes' :: DescribeFleetLocationAttributes -> Maybe Text
$sel:locations:DescribeFleetLocationAttributes' :: DescribeFleetLocationAttributes -> Maybe (NonEmpty Text)
$sel:limit:DescribeFleetLocationAttributes' :: DescribeFleetLocationAttributes -> Maybe Natural
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
limit
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Text)
locations
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
fleetId

instance
  Prelude.NFData
    DescribeFleetLocationAttributes
  where
  rnf :: DescribeFleetLocationAttributes -> ()
rnf DescribeFleetLocationAttributes' {Maybe Natural
Maybe (NonEmpty Text)
Maybe Text
Text
fleetId :: Text
nextToken :: Maybe Text
locations :: Maybe (NonEmpty Text)
limit :: Maybe Natural
$sel:fleetId:DescribeFleetLocationAttributes' :: DescribeFleetLocationAttributes -> Text
$sel:nextToken:DescribeFleetLocationAttributes' :: DescribeFleetLocationAttributes -> Maybe Text
$sel:locations:DescribeFleetLocationAttributes' :: DescribeFleetLocationAttributes -> Maybe (NonEmpty Text)
$sel:limit:DescribeFleetLocationAttributes' :: DescribeFleetLocationAttributes -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
limit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
locations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
fleetId

instance
  Data.ToHeaders
    DescribeFleetLocationAttributes
  where
  toHeaders :: DescribeFleetLocationAttributes -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"GameLift.DescribeFleetLocationAttributes" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DescribeFleetLocationAttributes where
  toJSON :: DescribeFleetLocationAttributes -> Value
toJSON DescribeFleetLocationAttributes' {Maybe Natural
Maybe (NonEmpty Text)
Maybe Text
Text
fleetId :: Text
nextToken :: Maybe Text
locations :: Maybe (NonEmpty Text)
limit :: Maybe Natural
$sel:fleetId:DescribeFleetLocationAttributes' :: DescribeFleetLocationAttributes -> Text
$sel:nextToken:DescribeFleetLocationAttributes' :: DescribeFleetLocationAttributes -> Maybe Text
$sel:locations:DescribeFleetLocationAttributes' :: DescribeFleetLocationAttributes -> Maybe (NonEmpty Text)
$sel:limit:DescribeFleetLocationAttributes' :: DescribeFleetLocationAttributes -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Limit" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
limit,
            (Key
"Locations" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (NonEmpty Text)
locations,
            (Key
"NextToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
nextToken,
            forall a. a -> Maybe a
Prelude.Just (Key
"FleetId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
fleetId)
          ]
      )

instance Data.ToPath DescribeFleetLocationAttributes where
  toPath :: DescribeFleetLocationAttributes -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery DescribeFleetLocationAttributes where
  toQuery :: DescribeFleetLocationAttributes -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newDescribeFleetLocationAttributesResponse' smart constructor.
data DescribeFleetLocationAttributesResponse = DescribeFleetLocationAttributesResponse'
  { -- | 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@.
    DescribeFleetLocationAttributesResponse -> Maybe Text
fleetArn :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the fleet that location attributes were
    -- requested for.
    DescribeFleetLocationAttributesResponse -> Maybe Text
fleetId :: Prelude.Maybe Prelude.Text,
    -- | Location-specific information on the requested fleet\'s remote
    -- locations.
    DescribeFleetLocationAttributesResponse
-> Maybe [LocationAttributes]
locationAttributes :: Prelude.Maybe [LocationAttributes],
    -- | A token that indicates where to resume retrieving results on the next
    -- call to this operation. If no token is returned, these results represent
    -- the end of the list.
    DescribeFleetLocationAttributesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeFleetLocationAttributesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeFleetLocationAttributesResponse
-> DescribeFleetLocationAttributesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeFleetLocationAttributesResponse
-> DescribeFleetLocationAttributesResponse -> Bool
$c/= :: DescribeFleetLocationAttributesResponse
-> DescribeFleetLocationAttributesResponse -> Bool
== :: DescribeFleetLocationAttributesResponse
-> DescribeFleetLocationAttributesResponse -> Bool
$c== :: DescribeFleetLocationAttributesResponse
-> DescribeFleetLocationAttributesResponse -> Bool
Prelude.Eq, ReadPrec [DescribeFleetLocationAttributesResponse]
ReadPrec DescribeFleetLocationAttributesResponse
Int -> ReadS DescribeFleetLocationAttributesResponse
ReadS [DescribeFleetLocationAttributesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeFleetLocationAttributesResponse]
$creadListPrec :: ReadPrec [DescribeFleetLocationAttributesResponse]
readPrec :: ReadPrec DescribeFleetLocationAttributesResponse
$creadPrec :: ReadPrec DescribeFleetLocationAttributesResponse
readList :: ReadS [DescribeFleetLocationAttributesResponse]
$creadList :: ReadS [DescribeFleetLocationAttributesResponse]
readsPrec :: Int -> ReadS DescribeFleetLocationAttributesResponse
$creadsPrec :: Int -> ReadS DescribeFleetLocationAttributesResponse
Prelude.Read, Int -> DescribeFleetLocationAttributesResponse -> ShowS
[DescribeFleetLocationAttributesResponse] -> ShowS
DescribeFleetLocationAttributesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeFleetLocationAttributesResponse] -> ShowS
$cshowList :: [DescribeFleetLocationAttributesResponse] -> ShowS
show :: DescribeFleetLocationAttributesResponse -> String
$cshow :: DescribeFleetLocationAttributesResponse -> String
showsPrec :: Int -> DescribeFleetLocationAttributesResponse -> ShowS
$cshowsPrec :: Int -> DescribeFleetLocationAttributesResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeFleetLocationAttributesResponse x
-> DescribeFleetLocationAttributesResponse
forall x.
DescribeFleetLocationAttributesResponse
-> Rep DescribeFleetLocationAttributesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeFleetLocationAttributesResponse x
-> DescribeFleetLocationAttributesResponse
$cfrom :: forall x.
DescribeFleetLocationAttributesResponse
-> Rep DescribeFleetLocationAttributesResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeFleetLocationAttributesResponse' 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', 'describeFleetLocationAttributesResponse_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', 'describeFleetLocationAttributesResponse_fleetId' - A unique identifier for the fleet that location attributes were
-- requested for.
--
-- 'locationAttributes', 'describeFleetLocationAttributesResponse_locationAttributes' - Location-specific information on the requested fleet\'s remote
-- locations.
--
-- 'nextToken', 'describeFleetLocationAttributesResponse_nextToken' - A token that indicates where to resume retrieving results on the next
-- call to this operation. If no token is returned, these results represent
-- the end of the list.
--
-- 'httpStatus', 'describeFleetLocationAttributesResponse_httpStatus' - The response's http status code.
newDescribeFleetLocationAttributesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeFleetLocationAttributesResponse
newDescribeFleetLocationAttributesResponse :: Int -> DescribeFleetLocationAttributesResponse
newDescribeFleetLocationAttributesResponse
  Int
pHttpStatus_ =
    DescribeFleetLocationAttributesResponse'
      { $sel:fleetArn:DescribeFleetLocationAttributesResponse' :: Maybe Text
fleetArn =
          forall a. Maybe a
Prelude.Nothing,
        $sel:fleetId:DescribeFleetLocationAttributesResponse' :: Maybe Text
fleetId = forall a. Maybe a
Prelude.Nothing,
        $sel:locationAttributes:DescribeFleetLocationAttributesResponse' :: Maybe [LocationAttributes]
locationAttributes =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:DescribeFleetLocationAttributesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeFleetLocationAttributesResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

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

-- | A unique identifier for the fleet that location attributes were
-- requested for.
describeFleetLocationAttributesResponse_fleetId :: Lens.Lens' DescribeFleetLocationAttributesResponse (Prelude.Maybe Prelude.Text)
describeFleetLocationAttributesResponse_fleetId :: Lens' DescribeFleetLocationAttributesResponse (Maybe Text)
describeFleetLocationAttributesResponse_fleetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFleetLocationAttributesResponse' {Maybe Text
fleetId :: Maybe Text
$sel:fleetId:DescribeFleetLocationAttributesResponse' :: DescribeFleetLocationAttributesResponse -> Maybe Text
fleetId} -> Maybe Text
fleetId) (\s :: DescribeFleetLocationAttributesResponse
s@DescribeFleetLocationAttributesResponse' {} Maybe Text
a -> DescribeFleetLocationAttributesResponse
s {$sel:fleetId:DescribeFleetLocationAttributesResponse' :: Maybe Text
fleetId = Maybe Text
a} :: DescribeFleetLocationAttributesResponse)

-- | Location-specific information on the requested fleet\'s remote
-- locations.
describeFleetLocationAttributesResponse_locationAttributes :: Lens.Lens' DescribeFleetLocationAttributesResponse (Prelude.Maybe [LocationAttributes])
describeFleetLocationAttributesResponse_locationAttributes :: Lens'
  DescribeFleetLocationAttributesResponse
  (Maybe [LocationAttributes])
describeFleetLocationAttributesResponse_locationAttributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFleetLocationAttributesResponse' {Maybe [LocationAttributes]
locationAttributes :: Maybe [LocationAttributes]
$sel:locationAttributes:DescribeFleetLocationAttributesResponse' :: DescribeFleetLocationAttributesResponse
-> Maybe [LocationAttributes]
locationAttributes} -> Maybe [LocationAttributes]
locationAttributes) (\s :: DescribeFleetLocationAttributesResponse
s@DescribeFleetLocationAttributesResponse' {} Maybe [LocationAttributes]
a -> DescribeFleetLocationAttributesResponse
s {$sel:locationAttributes:DescribeFleetLocationAttributesResponse' :: Maybe [LocationAttributes]
locationAttributes = Maybe [LocationAttributes]
a} :: DescribeFleetLocationAttributesResponse) 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 token that indicates where to resume retrieving results on the next
-- call to this operation. If no token is returned, these results represent
-- the end of the list.
describeFleetLocationAttributesResponse_nextToken :: Lens.Lens' DescribeFleetLocationAttributesResponse (Prelude.Maybe Prelude.Text)
describeFleetLocationAttributesResponse_nextToken :: Lens' DescribeFleetLocationAttributesResponse (Maybe Text)
describeFleetLocationAttributesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFleetLocationAttributesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeFleetLocationAttributesResponse' :: DescribeFleetLocationAttributesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeFleetLocationAttributesResponse
s@DescribeFleetLocationAttributesResponse' {} Maybe Text
a -> DescribeFleetLocationAttributesResponse
s {$sel:nextToken:DescribeFleetLocationAttributesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeFleetLocationAttributesResponse)

-- | The response's http status code.
describeFleetLocationAttributesResponse_httpStatus :: Lens.Lens' DescribeFleetLocationAttributesResponse Prelude.Int
describeFleetLocationAttributesResponse_httpStatus :: Lens' DescribeFleetLocationAttributesResponse Int
describeFleetLocationAttributesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeFleetLocationAttributesResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeFleetLocationAttributesResponse' :: DescribeFleetLocationAttributesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeFleetLocationAttributesResponse
s@DescribeFleetLocationAttributesResponse' {} Int
a -> DescribeFleetLocationAttributesResponse
s {$sel:httpStatus:DescribeFleetLocationAttributesResponse' :: Int
httpStatus = Int
a} :: DescribeFleetLocationAttributesResponse)

instance
  Prelude.NFData
    DescribeFleetLocationAttributesResponse
  where
  rnf :: DescribeFleetLocationAttributesResponse -> ()
rnf DescribeFleetLocationAttributesResponse' {Int
Maybe [LocationAttributes]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
locationAttributes :: Maybe [LocationAttributes]
fleetId :: Maybe Text
fleetArn :: Maybe Text
$sel:httpStatus:DescribeFleetLocationAttributesResponse' :: DescribeFleetLocationAttributesResponse -> Int
$sel:nextToken:DescribeFleetLocationAttributesResponse' :: DescribeFleetLocationAttributesResponse -> Maybe Text
$sel:locationAttributes:DescribeFleetLocationAttributesResponse' :: DescribeFleetLocationAttributesResponse
-> Maybe [LocationAttributes]
$sel:fleetId:DescribeFleetLocationAttributesResponse' :: DescribeFleetLocationAttributesResponse -> Maybe Text
$sel:fleetArn:DescribeFleetLocationAttributesResponse' :: DescribeFleetLocationAttributesResponse -> 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 [LocationAttributes]
locationAttributes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus