{-# 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.GameSessionPlacement
-- 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.GameSessionPlacement 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.GameProperty
import Amazonka.GameLift.Types.GameSessionPlacementState
import Amazonka.GameLift.Types.PlacedPlayerSession
import Amazonka.GameLift.Types.PlayerLatency
import qualified Amazonka.Prelude as Prelude

-- | This object includes the full details of the original request plus the
-- current status and start\/end time stamps.
--
-- /See:/ 'newGameSessionPlacement' smart constructor.
data GameSessionPlacement = GameSessionPlacement'
  { -- | The DNS identifier assigned to the instance that is running the game
    -- session. Values have the following format:
    --
    -- -   TLS-enabled fleets:
    --     @\<unique identifier>.\<region identifier>.amazongamelift.com@.
    --
    -- -   Non-TLS-enabled fleets:
    --     @ec2-\<unique identifier>.compute.amazonaws.com@. (See
    --     <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/using-instance-addressing.html#concepts-public-addresses Amazon EC2 Instance IP Addressing>.)
    --
    -- When connecting to a game session that is running on a TLS-enabled
    -- fleet, you must use the DNS name, not the IP address.
    GameSessionPlacement -> Maybe Text
dnsName :: Prelude.Maybe Prelude.Text,
    -- | Time stamp indicating when this request was completed, canceled, or
    -- timed out.
    GameSessionPlacement -> Maybe POSIX
endTime :: Prelude.Maybe Data.POSIX,
    -- | A set of custom properties for a game session, formatted as key:value
    -- pairs. These properties are passed to a game server process with a
    -- request to start a new game session (see
    -- <https://docs.aws.amazon.com/gamelift/latest/developerguide/gamelift-sdk-server-api.html#gamelift-sdk-server-startsession Start a Game Session>).
    GameSessionPlacement -> Maybe [GameProperty]
gameProperties :: Prelude.Maybe [GameProperty],
    -- | Identifier for the game session created by this placement request. This
    -- value is set once the new game session is placed (placement status is
    -- @FULFILLED@). This identifier is unique across all Regions. You can use
    -- this value as a @GameSessionId@ value as needed.
    GameSessionPlacement -> Maybe Text
gameSessionArn :: Prelude.Maybe Prelude.Text,
    -- | A set of custom game session properties, formatted as a single string
    -- value. This data is passed to a game server process in the @GameSession@
    -- object with a request to start a new game session (see
    -- <https://docs.aws.amazon.com/gamelift/latest/developerguide/gamelift-sdk-server-api.html#gamelift-sdk-server-startsession Start a Game Session>).
    GameSessionPlacement -> Maybe Text
gameSessionData :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the game session. This value is set once the new
    -- game session is placed (placement status is @FULFILLED@).
    GameSessionPlacement -> Maybe Text
gameSessionId :: Prelude.Maybe Prelude.Text,
    -- | A descriptive label that is associated with a game session. Session
    -- names do not need to be unique.
    GameSessionPlacement -> Maybe Text
gameSessionName :: Prelude.Maybe Prelude.Text,
    -- | A descriptive label that is associated with game session queue. Queue
    -- names must be unique within each Region.
    GameSessionPlacement -> Maybe Text
gameSessionQueueName :: Prelude.Maybe Prelude.Text,
    -- | Name of the Region where the game session created by this placement
    -- request is running. This value is set once the new game session is
    -- placed (placement status is @FULFILLED@).
    GameSessionPlacement -> Maybe Text
gameSessionRegion :: Prelude.Maybe Prelude.Text,
    -- | The IP address of the game session. To connect to a GameLift game
    -- server, an app needs both the IP address and port number. This value is
    -- set once the new game session is placed (placement status is
    -- @FULFILLED@).
    GameSessionPlacement -> Maybe Text
ipAddress :: Prelude.Maybe Prelude.Text,
    -- | Information on the matchmaking process for this game. Data is in JSON
    -- syntax, formatted as a string. It identifies the matchmaking
    -- configuration used to create the match, and contains data on all players
    -- assigned to the match, including player attributes and team assignments.
    -- For more details on matchmaker data, see
    -- <https://docs.aws.amazon.com/gamelift/latest/flexmatchguide/match-server.html#match-server-data Match Data>.
    GameSessionPlacement -> Maybe Text
matchmakerData :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of players that can be connected simultaneously to
    -- the game session.
    GameSessionPlacement -> Maybe Natural
maximumPlayerSessionCount :: Prelude.Maybe Prelude.Natural,
    -- | A collection of information on player sessions created in response to
    -- the game session placement request. These player sessions are created
    -- only once a new game session is successfully placed (placement status is
    -- @FULFILLED@). This information includes the player ID (as provided in
    -- the placement request) and the corresponding player session ID.
    GameSessionPlacement -> Maybe [PlacedPlayerSession]
placedPlayerSessions :: Prelude.Maybe [PlacedPlayerSession],
    -- | A unique identifier for a game session placement.
    GameSessionPlacement -> Maybe Text
placementId :: Prelude.Maybe Prelude.Text,
    -- | A set of values, expressed in milliseconds, that indicates the amount of
    -- latency that a player experiences when connected to Amazon Web Services
    -- Regions.
    GameSessionPlacement -> Maybe [PlayerLatency]
playerLatencies :: Prelude.Maybe [PlayerLatency],
    -- | The port number for the game session. To connect to a GameLift game
    -- server, an app needs both the IP address and port number. This value is
    -- set once the new game session is placed (placement status is
    -- @FULFILLED@).
    GameSessionPlacement -> Maybe Natural
port :: Prelude.Maybe Prelude.Natural,
    -- | Time stamp indicating when this request was placed in the queue. Format
    -- is a number expressed in Unix time as milliseconds (for example
    -- @\"1469498468.057\"@).
    GameSessionPlacement -> Maybe POSIX
startTime :: Prelude.Maybe Data.POSIX,
    -- | Current status of the game session placement request.
    --
    -- -   __PENDING__ -- The placement request is currently in the queue
    --     waiting to be processed.
    --
    -- -   __FULFILLED__ -- A new game session and player sessions (if
    --     requested) have been successfully created. Values for
    --     /GameSessionArn/ and /GameSessionRegion/ are available.
    --
    -- -   __CANCELLED__ -- The placement request was canceled.
    --
    -- -   __TIMED_OUT__ -- A new game session was not successfully created
    --     before the time limit expired. You can resubmit the placement
    --     request as needed.
    --
    -- -   __FAILED__ -- GameLift is not able to complete the process of
    --     placing the game session. Common reasons are the game session
    --     terminated before the placement process was completed, or an
    --     unexpected internal error.
    GameSessionPlacement -> Maybe GameSessionPlacementState
status :: Prelude.Maybe GameSessionPlacementState
  }
  deriving (GameSessionPlacement -> GameSessionPlacement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GameSessionPlacement -> GameSessionPlacement -> Bool
$c/= :: GameSessionPlacement -> GameSessionPlacement -> Bool
== :: GameSessionPlacement -> GameSessionPlacement -> Bool
$c== :: GameSessionPlacement -> GameSessionPlacement -> Bool
Prelude.Eq, ReadPrec [GameSessionPlacement]
ReadPrec GameSessionPlacement
Int -> ReadS GameSessionPlacement
ReadS [GameSessionPlacement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GameSessionPlacement]
$creadListPrec :: ReadPrec [GameSessionPlacement]
readPrec :: ReadPrec GameSessionPlacement
$creadPrec :: ReadPrec GameSessionPlacement
readList :: ReadS [GameSessionPlacement]
$creadList :: ReadS [GameSessionPlacement]
readsPrec :: Int -> ReadS GameSessionPlacement
$creadsPrec :: Int -> ReadS GameSessionPlacement
Prelude.Read, Int -> GameSessionPlacement -> ShowS
[GameSessionPlacement] -> ShowS
GameSessionPlacement -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GameSessionPlacement] -> ShowS
$cshowList :: [GameSessionPlacement] -> ShowS
show :: GameSessionPlacement -> String
$cshow :: GameSessionPlacement -> String
showsPrec :: Int -> GameSessionPlacement -> ShowS
$cshowsPrec :: Int -> GameSessionPlacement -> ShowS
Prelude.Show, forall x. Rep GameSessionPlacement x -> GameSessionPlacement
forall x. GameSessionPlacement -> Rep GameSessionPlacement x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GameSessionPlacement x -> GameSessionPlacement
$cfrom :: forall x. GameSessionPlacement -> Rep GameSessionPlacement x
Prelude.Generic)

-- |
-- Create a value of 'GameSessionPlacement' 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:
--
-- 'dnsName', 'gameSessionPlacement_dnsName' - The DNS identifier assigned to the instance that is running the game
-- session. Values have the following format:
--
-- -   TLS-enabled fleets:
--     @\<unique identifier>.\<region identifier>.amazongamelift.com@.
--
-- -   Non-TLS-enabled fleets:
--     @ec2-\<unique identifier>.compute.amazonaws.com@. (See
--     <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/using-instance-addressing.html#concepts-public-addresses Amazon EC2 Instance IP Addressing>.)
--
-- When connecting to a game session that is running on a TLS-enabled
-- fleet, you must use the DNS name, not the IP address.
--
-- 'endTime', 'gameSessionPlacement_endTime' - Time stamp indicating when this request was completed, canceled, or
-- timed out.
--
-- 'gameProperties', 'gameSessionPlacement_gameProperties' - A set of custom properties for a game session, formatted as key:value
-- pairs. These properties are passed to a game server process with a
-- request to start a new game session (see
-- <https://docs.aws.amazon.com/gamelift/latest/developerguide/gamelift-sdk-server-api.html#gamelift-sdk-server-startsession Start a Game Session>).
--
-- 'gameSessionArn', 'gameSessionPlacement_gameSessionArn' - Identifier for the game session created by this placement request. This
-- value is set once the new game session is placed (placement status is
-- @FULFILLED@). This identifier is unique across all Regions. You can use
-- this value as a @GameSessionId@ value as needed.
--
-- 'gameSessionData', 'gameSessionPlacement_gameSessionData' - A set of custom game session properties, formatted as a single string
-- value. This data is passed to a game server process in the @GameSession@
-- object with a request to start a new game session (see
-- <https://docs.aws.amazon.com/gamelift/latest/developerguide/gamelift-sdk-server-api.html#gamelift-sdk-server-startsession Start a Game Session>).
--
-- 'gameSessionId', 'gameSessionPlacement_gameSessionId' - A unique identifier for the game session. This value is set once the new
-- game session is placed (placement status is @FULFILLED@).
--
-- 'gameSessionName', 'gameSessionPlacement_gameSessionName' - A descriptive label that is associated with a game session. Session
-- names do not need to be unique.
--
-- 'gameSessionQueueName', 'gameSessionPlacement_gameSessionQueueName' - A descriptive label that is associated with game session queue. Queue
-- names must be unique within each Region.
--
-- 'gameSessionRegion', 'gameSessionPlacement_gameSessionRegion' - Name of the Region where the game session created by this placement
-- request is running. This value is set once the new game session is
-- placed (placement status is @FULFILLED@).
--
-- 'ipAddress', 'gameSessionPlacement_ipAddress' - The IP address of the game session. To connect to a GameLift game
-- server, an app needs both the IP address and port number. This value is
-- set once the new game session is placed (placement status is
-- @FULFILLED@).
--
-- 'matchmakerData', 'gameSessionPlacement_matchmakerData' - Information on the matchmaking process for this game. Data is in JSON
-- syntax, formatted as a string. It identifies the matchmaking
-- configuration used to create the match, and contains data on all players
-- assigned to the match, including player attributes and team assignments.
-- For more details on matchmaker data, see
-- <https://docs.aws.amazon.com/gamelift/latest/flexmatchguide/match-server.html#match-server-data Match Data>.
--
-- 'maximumPlayerSessionCount', 'gameSessionPlacement_maximumPlayerSessionCount' - The maximum number of players that can be connected simultaneously to
-- the game session.
--
-- 'placedPlayerSessions', 'gameSessionPlacement_placedPlayerSessions' - A collection of information on player sessions created in response to
-- the game session placement request. These player sessions are created
-- only once a new game session is successfully placed (placement status is
-- @FULFILLED@). This information includes the player ID (as provided in
-- the placement request) and the corresponding player session ID.
--
-- 'placementId', 'gameSessionPlacement_placementId' - A unique identifier for a game session placement.
--
-- 'playerLatencies', 'gameSessionPlacement_playerLatencies' - A set of values, expressed in milliseconds, that indicates the amount of
-- latency that a player experiences when connected to Amazon Web Services
-- Regions.
--
-- 'port', 'gameSessionPlacement_port' - The port number for the game session. To connect to a GameLift game
-- server, an app needs both the IP address and port number. This value is
-- set once the new game session is placed (placement status is
-- @FULFILLED@).
--
-- 'startTime', 'gameSessionPlacement_startTime' - Time stamp indicating when this request was placed in the queue. Format
-- is a number expressed in Unix time as milliseconds (for example
-- @\"1469498468.057\"@).
--
-- 'status', 'gameSessionPlacement_status' - Current status of the game session placement request.
--
-- -   __PENDING__ -- The placement request is currently in the queue
--     waiting to be processed.
--
-- -   __FULFILLED__ -- A new game session and player sessions (if
--     requested) have been successfully created. Values for
--     /GameSessionArn/ and /GameSessionRegion/ are available.
--
-- -   __CANCELLED__ -- The placement request was canceled.
--
-- -   __TIMED_OUT__ -- A new game session was not successfully created
--     before the time limit expired. You can resubmit the placement
--     request as needed.
--
-- -   __FAILED__ -- GameLift is not able to complete the process of
--     placing the game session. Common reasons are the game session
--     terminated before the placement process was completed, or an
--     unexpected internal error.
newGameSessionPlacement ::
  GameSessionPlacement
newGameSessionPlacement :: GameSessionPlacement
newGameSessionPlacement =
  GameSessionPlacement'
    { $sel:dnsName:GameSessionPlacement' :: Maybe Text
dnsName = forall a. Maybe a
Prelude.Nothing,
      $sel:endTime:GameSessionPlacement' :: Maybe POSIX
endTime = forall a. Maybe a
Prelude.Nothing,
      $sel:gameProperties:GameSessionPlacement' :: Maybe [GameProperty]
gameProperties = forall a. Maybe a
Prelude.Nothing,
      $sel:gameSessionArn:GameSessionPlacement' :: Maybe Text
gameSessionArn = forall a. Maybe a
Prelude.Nothing,
      $sel:gameSessionData:GameSessionPlacement' :: Maybe Text
gameSessionData = forall a. Maybe a
Prelude.Nothing,
      $sel:gameSessionId:GameSessionPlacement' :: Maybe Text
gameSessionId = forall a. Maybe a
Prelude.Nothing,
      $sel:gameSessionName:GameSessionPlacement' :: Maybe Text
gameSessionName = forall a. Maybe a
Prelude.Nothing,
      $sel:gameSessionQueueName:GameSessionPlacement' :: Maybe Text
gameSessionQueueName = forall a. Maybe a
Prelude.Nothing,
      $sel:gameSessionRegion:GameSessionPlacement' :: Maybe Text
gameSessionRegion = forall a. Maybe a
Prelude.Nothing,
      $sel:ipAddress:GameSessionPlacement' :: Maybe Text
ipAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:matchmakerData:GameSessionPlacement' :: Maybe Text
matchmakerData = forall a. Maybe a
Prelude.Nothing,
      $sel:maximumPlayerSessionCount:GameSessionPlacement' :: Maybe Natural
maximumPlayerSessionCount = forall a. Maybe a
Prelude.Nothing,
      $sel:placedPlayerSessions:GameSessionPlacement' :: Maybe [PlacedPlayerSession]
placedPlayerSessions = forall a. Maybe a
Prelude.Nothing,
      $sel:placementId:GameSessionPlacement' :: Maybe Text
placementId = forall a. Maybe a
Prelude.Nothing,
      $sel:playerLatencies:GameSessionPlacement' :: Maybe [PlayerLatency]
playerLatencies = forall a. Maybe a
Prelude.Nothing,
      $sel:port:GameSessionPlacement' :: Maybe Natural
port = forall a. Maybe a
Prelude.Nothing,
      $sel:startTime:GameSessionPlacement' :: Maybe POSIX
startTime = forall a. Maybe a
Prelude.Nothing,
      $sel:status:GameSessionPlacement' :: Maybe GameSessionPlacementState
status = forall a. Maybe a
Prelude.Nothing
    }

-- | The DNS identifier assigned to the instance that is running the game
-- session. Values have the following format:
--
-- -   TLS-enabled fleets:
--     @\<unique identifier>.\<region identifier>.amazongamelift.com@.
--
-- -   Non-TLS-enabled fleets:
--     @ec2-\<unique identifier>.compute.amazonaws.com@. (See
--     <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/using-instance-addressing.html#concepts-public-addresses Amazon EC2 Instance IP Addressing>.)
--
-- When connecting to a game session that is running on a TLS-enabled
-- fleet, you must use the DNS name, not the IP address.
gameSessionPlacement_dnsName :: Lens.Lens' GameSessionPlacement (Prelude.Maybe Prelude.Text)
gameSessionPlacement_dnsName :: Lens' GameSessionPlacement (Maybe Text)
gameSessionPlacement_dnsName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GameSessionPlacement' {Maybe Text
dnsName :: Maybe Text
$sel:dnsName:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
dnsName} -> Maybe Text
dnsName) (\s :: GameSessionPlacement
s@GameSessionPlacement' {} Maybe Text
a -> GameSessionPlacement
s {$sel:dnsName:GameSessionPlacement' :: Maybe Text
dnsName = Maybe Text
a} :: GameSessionPlacement)

-- | Time stamp indicating when this request was completed, canceled, or
-- timed out.
gameSessionPlacement_endTime :: Lens.Lens' GameSessionPlacement (Prelude.Maybe Prelude.UTCTime)
gameSessionPlacement_endTime :: Lens' GameSessionPlacement (Maybe UTCTime)
gameSessionPlacement_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GameSessionPlacement' {Maybe POSIX
endTime :: Maybe POSIX
$sel:endTime:GameSessionPlacement' :: GameSessionPlacement -> Maybe POSIX
endTime} -> Maybe POSIX
endTime) (\s :: GameSessionPlacement
s@GameSessionPlacement' {} Maybe POSIX
a -> GameSessionPlacement
s {$sel:endTime:GameSessionPlacement' :: Maybe POSIX
endTime = Maybe POSIX
a} :: GameSessionPlacement) 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 set of custom properties for a game session, formatted as key:value
-- pairs. These properties are passed to a game server process with a
-- request to start a new game session (see
-- <https://docs.aws.amazon.com/gamelift/latest/developerguide/gamelift-sdk-server-api.html#gamelift-sdk-server-startsession Start a Game Session>).
gameSessionPlacement_gameProperties :: Lens.Lens' GameSessionPlacement (Prelude.Maybe [GameProperty])
gameSessionPlacement_gameProperties :: Lens' GameSessionPlacement (Maybe [GameProperty])
gameSessionPlacement_gameProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GameSessionPlacement' {Maybe [GameProperty]
gameProperties :: Maybe [GameProperty]
$sel:gameProperties:GameSessionPlacement' :: GameSessionPlacement -> Maybe [GameProperty]
gameProperties} -> Maybe [GameProperty]
gameProperties) (\s :: GameSessionPlacement
s@GameSessionPlacement' {} Maybe [GameProperty]
a -> GameSessionPlacement
s {$sel:gameProperties:GameSessionPlacement' :: Maybe [GameProperty]
gameProperties = Maybe [GameProperty]
a} :: GameSessionPlacement) 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

-- | Identifier for the game session created by this placement request. This
-- value is set once the new game session is placed (placement status is
-- @FULFILLED@). This identifier is unique across all Regions. You can use
-- this value as a @GameSessionId@ value as needed.
gameSessionPlacement_gameSessionArn :: Lens.Lens' GameSessionPlacement (Prelude.Maybe Prelude.Text)
gameSessionPlacement_gameSessionArn :: Lens' GameSessionPlacement (Maybe Text)
gameSessionPlacement_gameSessionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GameSessionPlacement' {Maybe Text
gameSessionArn :: Maybe Text
$sel:gameSessionArn:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
gameSessionArn} -> Maybe Text
gameSessionArn) (\s :: GameSessionPlacement
s@GameSessionPlacement' {} Maybe Text
a -> GameSessionPlacement
s {$sel:gameSessionArn:GameSessionPlacement' :: Maybe Text
gameSessionArn = Maybe Text
a} :: GameSessionPlacement)

-- | A set of custom game session properties, formatted as a single string
-- value. This data is passed to a game server process in the @GameSession@
-- object with a request to start a new game session (see
-- <https://docs.aws.amazon.com/gamelift/latest/developerguide/gamelift-sdk-server-api.html#gamelift-sdk-server-startsession Start a Game Session>).
gameSessionPlacement_gameSessionData :: Lens.Lens' GameSessionPlacement (Prelude.Maybe Prelude.Text)
gameSessionPlacement_gameSessionData :: Lens' GameSessionPlacement (Maybe Text)
gameSessionPlacement_gameSessionData = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GameSessionPlacement' {Maybe Text
gameSessionData :: Maybe Text
$sel:gameSessionData:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
gameSessionData} -> Maybe Text
gameSessionData) (\s :: GameSessionPlacement
s@GameSessionPlacement' {} Maybe Text
a -> GameSessionPlacement
s {$sel:gameSessionData:GameSessionPlacement' :: Maybe Text
gameSessionData = Maybe Text
a} :: GameSessionPlacement)

-- | A unique identifier for the game session. This value is set once the new
-- game session is placed (placement status is @FULFILLED@).
gameSessionPlacement_gameSessionId :: Lens.Lens' GameSessionPlacement (Prelude.Maybe Prelude.Text)
gameSessionPlacement_gameSessionId :: Lens' GameSessionPlacement (Maybe Text)
gameSessionPlacement_gameSessionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GameSessionPlacement' {Maybe Text
gameSessionId :: Maybe Text
$sel:gameSessionId:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
gameSessionId} -> Maybe Text
gameSessionId) (\s :: GameSessionPlacement
s@GameSessionPlacement' {} Maybe Text
a -> GameSessionPlacement
s {$sel:gameSessionId:GameSessionPlacement' :: Maybe Text
gameSessionId = Maybe Text
a} :: GameSessionPlacement)

-- | A descriptive label that is associated with a game session. Session
-- names do not need to be unique.
gameSessionPlacement_gameSessionName :: Lens.Lens' GameSessionPlacement (Prelude.Maybe Prelude.Text)
gameSessionPlacement_gameSessionName :: Lens' GameSessionPlacement (Maybe Text)
gameSessionPlacement_gameSessionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GameSessionPlacement' {Maybe Text
gameSessionName :: Maybe Text
$sel:gameSessionName:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
gameSessionName} -> Maybe Text
gameSessionName) (\s :: GameSessionPlacement
s@GameSessionPlacement' {} Maybe Text
a -> GameSessionPlacement
s {$sel:gameSessionName:GameSessionPlacement' :: Maybe Text
gameSessionName = Maybe Text
a} :: GameSessionPlacement)

-- | A descriptive label that is associated with game session queue. Queue
-- names must be unique within each Region.
gameSessionPlacement_gameSessionQueueName :: Lens.Lens' GameSessionPlacement (Prelude.Maybe Prelude.Text)
gameSessionPlacement_gameSessionQueueName :: Lens' GameSessionPlacement (Maybe Text)
gameSessionPlacement_gameSessionQueueName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GameSessionPlacement' {Maybe Text
gameSessionQueueName :: Maybe Text
$sel:gameSessionQueueName:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
gameSessionQueueName} -> Maybe Text
gameSessionQueueName) (\s :: GameSessionPlacement
s@GameSessionPlacement' {} Maybe Text
a -> GameSessionPlacement
s {$sel:gameSessionQueueName:GameSessionPlacement' :: Maybe Text
gameSessionQueueName = Maybe Text
a} :: GameSessionPlacement)

-- | Name of the Region where the game session created by this placement
-- request is running. This value is set once the new game session is
-- placed (placement status is @FULFILLED@).
gameSessionPlacement_gameSessionRegion :: Lens.Lens' GameSessionPlacement (Prelude.Maybe Prelude.Text)
gameSessionPlacement_gameSessionRegion :: Lens' GameSessionPlacement (Maybe Text)
gameSessionPlacement_gameSessionRegion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GameSessionPlacement' {Maybe Text
gameSessionRegion :: Maybe Text
$sel:gameSessionRegion:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
gameSessionRegion} -> Maybe Text
gameSessionRegion) (\s :: GameSessionPlacement
s@GameSessionPlacement' {} Maybe Text
a -> GameSessionPlacement
s {$sel:gameSessionRegion:GameSessionPlacement' :: Maybe Text
gameSessionRegion = Maybe Text
a} :: GameSessionPlacement)

-- | The IP address of the game session. To connect to a GameLift game
-- server, an app needs both the IP address and port number. This value is
-- set once the new game session is placed (placement status is
-- @FULFILLED@).
gameSessionPlacement_ipAddress :: Lens.Lens' GameSessionPlacement (Prelude.Maybe Prelude.Text)
gameSessionPlacement_ipAddress :: Lens' GameSessionPlacement (Maybe Text)
gameSessionPlacement_ipAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GameSessionPlacement' {Maybe Text
ipAddress :: Maybe Text
$sel:ipAddress:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
ipAddress} -> Maybe Text
ipAddress) (\s :: GameSessionPlacement
s@GameSessionPlacement' {} Maybe Text
a -> GameSessionPlacement
s {$sel:ipAddress:GameSessionPlacement' :: Maybe Text
ipAddress = Maybe Text
a} :: GameSessionPlacement)

-- | Information on the matchmaking process for this game. Data is in JSON
-- syntax, formatted as a string. It identifies the matchmaking
-- configuration used to create the match, and contains data on all players
-- assigned to the match, including player attributes and team assignments.
-- For more details on matchmaker data, see
-- <https://docs.aws.amazon.com/gamelift/latest/flexmatchguide/match-server.html#match-server-data Match Data>.
gameSessionPlacement_matchmakerData :: Lens.Lens' GameSessionPlacement (Prelude.Maybe Prelude.Text)
gameSessionPlacement_matchmakerData :: Lens' GameSessionPlacement (Maybe Text)
gameSessionPlacement_matchmakerData = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GameSessionPlacement' {Maybe Text
matchmakerData :: Maybe Text
$sel:matchmakerData:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
matchmakerData} -> Maybe Text
matchmakerData) (\s :: GameSessionPlacement
s@GameSessionPlacement' {} Maybe Text
a -> GameSessionPlacement
s {$sel:matchmakerData:GameSessionPlacement' :: Maybe Text
matchmakerData = Maybe Text
a} :: GameSessionPlacement)

-- | The maximum number of players that can be connected simultaneously to
-- the game session.
gameSessionPlacement_maximumPlayerSessionCount :: Lens.Lens' GameSessionPlacement (Prelude.Maybe Prelude.Natural)
gameSessionPlacement_maximumPlayerSessionCount :: Lens' GameSessionPlacement (Maybe Natural)
gameSessionPlacement_maximumPlayerSessionCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GameSessionPlacement' {Maybe Natural
maximumPlayerSessionCount :: Maybe Natural
$sel:maximumPlayerSessionCount:GameSessionPlacement' :: GameSessionPlacement -> Maybe Natural
maximumPlayerSessionCount} -> Maybe Natural
maximumPlayerSessionCount) (\s :: GameSessionPlacement
s@GameSessionPlacement' {} Maybe Natural
a -> GameSessionPlacement
s {$sel:maximumPlayerSessionCount:GameSessionPlacement' :: Maybe Natural
maximumPlayerSessionCount = Maybe Natural
a} :: GameSessionPlacement)

-- | A collection of information on player sessions created in response to
-- the game session placement request. These player sessions are created
-- only once a new game session is successfully placed (placement status is
-- @FULFILLED@). This information includes the player ID (as provided in
-- the placement request) and the corresponding player session ID.
gameSessionPlacement_placedPlayerSessions :: Lens.Lens' GameSessionPlacement (Prelude.Maybe [PlacedPlayerSession])
gameSessionPlacement_placedPlayerSessions :: Lens' GameSessionPlacement (Maybe [PlacedPlayerSession])
gameSessionPlacement_placedPlayerSessions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GameSessionPlacement' {Maybe [PlacedPlayerSession]
placedPlayerSessions :: Maybe [PlacedPlayerSession]
$sel:placedPlayerSessions:GameSessionPlacement' :: GameSessionPlacement -> Maybe [PlacedPlayerSession]
placedPlayerSessions} -> Maybe [PlacedPlayerSession]
placedPlayerSessions) (\s :: GameSessionPlacement
s@GameSessionPlacement' {} Maybe [PlacedPlayerSession]
a -> GameSessionPlacement
s {$sel:placedPlayerSessions:GameSessionPlacement' :: Maybe [PlacedPlayerSession]
placedPlayerSessions = Maybe [PlacedPlayerSession]
a} :: GameSessionPlacement) 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 unique identifier for a game session placement.
gameSessionPlacement_placementId :: Lens.Lens' GameSessionPlacement (Prelude.Maybe Prelude.Text)
gameSessionPlacement_placementId :: Lens' GameSessionPlacement (Maybe Text)
gameSessionPlacement_placementId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GameSessionPlacement' {Maybe Text
placementId :: Maybe Text
$sel:placementId:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
placementId} -> Maybe Text
placementId) (\s :: GameSessionPlacement
s@GameSessionPlacement' {} Maybe Text
a -> GameSessionPlacement
s {$sel:placementId:GameSessionPlacement' :: Maybe Text
placementId = Maybe Text
a} :: GameSessionPlacement)

-- | A set of values, expressed in milliseconds, that indicates the amount of
-- latency that a player experiences when connected to Amazon Web Services
-- Regions.
gameSessionPlacement_playerLatencies :: Lens.Lens' GameSessionPlacement (Prelude.Maybe [PlayerLatency])
gameSessionPlacement_playerLatencies :: Lens' GameSessionPlacement (Maybe [PlayerLatency])
gameSessionPlacement_playerLatencies = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GameSessionPlacement' {Maybe [PlayerLatency]
playerLatencies :: Maybe [PlayerLatency]
$sel:playerLatencies:GameSessionPlacement' :: GameSessionPlacement -> Maybe [PlayerLatency]
playerLatencies} -> Maybe [PlayerLatency]
playerLatencies) (\s :: GameSessionPlacement
s@GameSessionPlacement' {} Maybe [PlayerLatency]
a -> GameSessionPlacement
s {$sel:playerLatencies:GameSessionPlacement' :: Maybe [PlayerLatency]
playerLatencies = Maybe [PlayerLatency]
a} :: GameSessionPlacement) 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

-- | The port number for the game session. To connect to a GameLift game
-- server, an app needs both the IP address and port number. This value is
-- set once the new game session is placed (placement status is
-- @FULFILLED@).
gameSessionPlacement_port :: Lens.Lens' GameSessionPlacement (Prelude.Maybe Prelude.Natural)
gameSessionPlacement_port :: Lens' GameSessionPlacement (Maybe Natural)
gameSessionPlacement_port = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GameSessionPlacement' {Maybe Natural
port :: Maybe Natural
$sel:port:GameSessionPlacement' :: GameSessionPlacement -> Maybe Natural
port} -> Maybe Natural
port) (\s :: GameSessionPlacement
s@GameSessionPlacement' {} Maybe Natural
a -> GameSessionPlacement
s {$sel:port:GameSessionPlacement' :: Maybe Natural
port = Maybe Natural
a} :: GameSessionPlacement)

-- | Time stamp indicating when this request was placed in the queue. Format
-- is a number expressed in Unix time as milliseconds (for example
-- @\"1469498468.057\"@).
gameSessionPlacement_startTime :: Lens.Lens' GameSessionPlacement (Prelude.Maybe Prelude.UTCTime)
gameSessionPlacement_startTime :: Lens' GameSessionPlacement (Maybe UTCTime)
gameSessionPlacement_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GameSessionPlacement' {Maybe POSIX
startTime :: Maybe POSIX
$sel:startTime:GameSessionPlacement' :: GameSessionPlacement -> Maybe POSIX
startTime} -> Maybe POSIX
startTime) (\s :: GameSessionPlacement
s@GameSessionPlacement' {} Maybe POSIX
a -> GameSessionPlacement
s {$sel:startTime:GameSessionPlacement' :: Maybe POSIX
startTime = Maybe POSIX
a} :: GameSessionPlacement) 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

-- | Current status of the game session placement request.
--
-- -   __PENDING__ -- The placement request is currently in the queue
--     waiting to be processed.
--
-- -   __FULFILLED__ -- A new game session and player sessions (if
--     requested) have been successfully created. Values for
--     /GameSessionArn/ and /GameSessionRegion/ are available.
--
-- -   __CANCELLED__ -- The placement request was canceled.
--
-- -   __TIMED_OUT__ -- A new game session was not successfully created
--     before the time limit expired. You can resubmit the placement
--     request as needed.
--
-- -   __FAILED__ -- GameLift is not able to complete the process of
--     placing the game session. Common reasons are the game session
--     terminated before the placement process was completed, or an
--     unexpected internal error.
gameSessionPlacement_status :: Lens.Lens' GameSessionPlacement (Prelude.Maybe GameSessionPlacementState)
gameSessionPlacement_status :: Lens' GameSessionPlacement (Maybe GameSessionPlacementState)
gameSessionPlacement_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GameSessionPlacement' {Maybe GameSessionPlacementState
status :: Maybe GameSessionPlacementState
$sel:status:GameSessionPlacement' :: GameSessionPlacement -> Maybe GameSessionPlacementState
status} -> Maybe GameSessionPlacementState
status) (\s :: GameSessionPlacement
s@GameSessionPlacement' {} Maybe GameSessionPlacementState
a -> GameSessionPlacement
s {$sel:status:GameSessionPlacement' :: Maybe GameSessionPlacementState
status = Maybe GameSessionPlacementState
a} :: GameSessionPlacement)

instance Data.FromJSON GameSessionPlacement where
  parseJSON :: Value -> Parser GameSessionPlacement
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"GameSessionPlacement"
      ( \Object
x ->
          Maybe Text
-> Maybe POSIX
-> Maybe [GameProperty]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Natural
-> Maybe [PlacedPlayerSession]
-> Maybe Text
-> Maybe [PlayerLatency]
-> Maybe Natural
-> Maybe POSIX
-> Maybe GameSessionPlacementState
-> GameSessionPlacement
GameSessionPlacement'
            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
"DnsName")
            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
"EndTime")
            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
"GameProperties" 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
"GameSessionArn")
            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
"GameSessionData")
            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
"GameSessionId")
            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
"GameSessionName")
            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
"GameSessionQueueName")
            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
"GameSessionRegion")
            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
"IpAddress")
            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
"MatchmakerData")
            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
"MaximumPlayerSessionCount")
            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
"PlacedPlayerSessions"
                            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
"PlacementId")
            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
"PlayerLatencies"
                            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
"Port")
            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
"StartTime")
            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")
      )

instance Prelude.Hashable GameSessionPlacement where
  hashWithSalt :: Int -> GameSessionPlacement -> Int
hashWithSalt Int
_salt GameSessionPlacement' {Maybe Natural
Maybe [GameProperty]
Maybe [PlacedPlayerSession]
Maybe [PlayerLatency]
Maybe Text
Maybe POSIX
Maybe GameSessionPlacementState
status :: Maybe GameSessionPlacementState
startTime :: Maybe POSIX
port :: Maybe Natural
playerLatencies :: Maybe [PlayerLatency]
placementId :: Maybe Text
placedPlayerSessions :: Maybe [PlacedPlayerSession]
maximumPlayerSessionCount :: Maybe Natural
matchmakerData :: Maybe Text
ipAddress :: Maybe Text
gameSessionRegion :: Maybe Text
gameSessionQueueName :: Maybe Text
gameSessionName :: Maybe Text
gameSessionId :: Maybe Text
gameSessionData :: Maybe Text
gameSessionArn :: Maybe Text
gameProperties :: Maybe [GameProperty]
endTime :: Maybe POSIX
dnsName :: Maybe Text
$sel:status:GameSessionPlacement' :: GameSessionPlacement -> Maybe GameSessionPlacementState
$sel:startTime:GameSessionPlacement' :: GameSessionPlacement -> Maybe POSIX
$sel:port:GameSessionPlacement' :: GameSessionPlacement -> Maybe Natural
$sel:playerLatencies:GameSessionPlacement' :: GameSessionPlacement -> Maybe [PlayerLatency]
$sel:placementId:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
$sel:placedPlayerSessions:GameSessionPlacement' :: GameSessionPlacement -> Maybe [PlacedPlayerSession]
$sel:maximumPlayerSessionCount:GameSessionPlacement' :: GameSessionPlacement -> Maybe Natural
$sel:matchmakerData:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
$sel:ipAddress:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
$sel:gameSessionRegion:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
$sel:gameSessionQueueName:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
$sel:gameSessionName:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
$sel:gameSessionId:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
$sel:gameSessionData:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
$sel:gameSessionArn:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
$sel:gameProperties:GameSessionPlacement' :: GameSessionPlacement -> Maybe [GameProperty]
$sel:endTime:GameSessionPlacement' :: GameSessionPlacement -> Maybe POSIX
$sel:dnsName:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dnsName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
endTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [GameProperty]
gameProperties
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
gameSessionArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
gameSessionData
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
gameSessionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
gameSessionName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
gameSessionQueueName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
gameSessionRegion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ipAddress
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
matchmakerData
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maximumPlayerSessionCount
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [PlacedPlayerSession]
placedPlayerSessions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
placementId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [PlayerLatency]
playerLatencies
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
port
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
startTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe GameSessionPlacementState
status

instance Prelude.NFData GameSessionPlacement where
  rnf :: GameSessionPlacement -> ()
rnf GameSessionPlacement' {Maybe Natural
Maybe [GameProperty]
Maybe [PlacedPlayerSession]
Maybe [PlayerLatency]
Maybe Text
Maybe POSIX
Maybe GameSessionPlacementState
status :: Maybe GameSessionPlacementState
startTime :: Maybe POSIX
port :: Maybe Natural
playerLatencies :: Maybe [PlayerLatency]
placementId :: Maybe Text
placedPlayerSessions :: Maybe [PlacedPlayerSession]
maximumPlayerSessionCount :: Maybe Natural
matchmakerData :: Maybe Text
ipAddress :: Maybe Text
gameSessionRegion :: Maybe Text
gameSessionQueueName :: Maybe Text
gameSessionName :: Maybe Text
gameSessionId :: Maybe Text
gameSessionData :: Maybe Text
gameSessionArn :: Maybe Text
gameProperties :: Maybe [GameProperty]
endTime :: Maybe POSIX
dnsName :: Maybe Text
$sel:status:GameSessionPlacement' :: GameSessionPlacement -> Maybe GameSessionPlacementState
$sel:startTime:GameSessionPlacement' :: GameSessionPlacement -> Maybe POSIX
$sel:port:GameSessionPlacement' :: GameSessionPlacement -> Maybe Natural
$sel:playerLatencies:GameSessionPlacement' :: GameSessionPlacement -> Maybe [PlayerLatency]
$sel:placementId:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
$sel:placedPlayerSessions:GameSessionPlacement' :: GameSessionPlacement -> Maybe [PlacedPlayerSession]
$sel:maximumPlayerSessionCount:GameSessionPlacement' :: GameSessionPlacement -> Maybe Natural
$sel:matchmakerData:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
$sel:ipAddress:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
$sel:gameSessionRegion:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
$sel:gameSessionQueueName:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
$sel:gameSessionName:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
$sel:gameSessionId:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
$sel:gameSessionData:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
$sel:gameSessionArn:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
$sel:gameProperties:GameSessionPlacement' :: GameSessionPlacement -> Maybe [GameProperty]
$sel:endTime:GameSessionPlacement' :: GameSessionPlacement -> Maybe POSIX
$sel:dnsName:GameSessionPlacement' :: GameSessionPlacement -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dnsName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
endTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [GameProperty]
gameProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
gameSessionArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
gameSessionData
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
gameSessionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
gameSessionName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
gameSessionQueueName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
gameSessionRegion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ipAddress
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
matchmakerData
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maximumPlayerSessionCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [PlacedPlayerSession]
placedPlayerSessions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
placementId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [PlayerLatency]
playerLatencies
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
port
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
startTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe GameSessionPlacementState
status