{-# 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.UpdateGameSession
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the mutable properties of a game session.
--
-- To update a game session, specify the game session ID and the values you
-- want to change.
--
-- If successful, the updated @GameSession@ object is returned.
--
-- <https://docs.aws.amazon.com/gamelift/latest/developerguide/reference-awssdk.html#reference-awssdk-resources-fleets All APIs by task>
module Amazonka.GameLift.UpdateGameSession
  ( -- * Creating a Request
    UpdateGameSession (..),
    newUpdateGameSession,

    -- * Request Lenses
    updateGameSession_maximumPlayerSessionCount,
    updateGameSession_name,
    updateGameSession_playerSessionCreationPolicy,
    updateGameSession_protectionPolicy,
    updateGameSession_gameSessionId,

    -- * Destructuring the Response
    UpdateGameSessionResponse (..),
    newUpdateGameSessionResponse,

    -- * Response Lenses
    updateGameSessionResponse_gameSession,
    updateGameSessionResponse_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:/ 'newUpdateGameSession' smart constructor.
data UpdateGameSession = UpdateGameSession'
  { -- | The maximum number of players that can be connected simultaneously to
    -- the game session.
    UpdateGameSession -> Maybe Natural
maximumPlayerSessionCount :: Prelude.Maybe Prelude.Natural,
    -- | A descriptive label that is associated with a game session. Session
    -- names do not need to be unique.
    UpdateGameSession -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | A policy that determines whether the game session is accepting new
    -- players.
    UpdateGameSession -> Maybe PlayerSessionCreationPolicy
playerSessionCreationPolicy :: Prelude.Maybe PlayerSessionCreationPolicy,
    -- | Game session protection policy to apply to this game session only.
    --
    -- -   __NoProtection__ -- The game session can be terminated during a
    --     scale-down event.
    --
    -- -   __FullProtection__ -- If the game session is in an @ACTIVE@ status,
    --     it cannot be terminated during a scale-down event.
    UpdateGameSession -> Maybe ProtectionPolicy
protectionPolicy :: Prelude.Maybe ProtectionPolicy,
    -- | A unique identifier for the game session to update.
    UpdateGameSession -> Text
gameSessionId :: Prelude.Text
  }
  deriving (UpdateGameSession -> UpdateGameSession -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateGameSession -> UpdateGameSession -> Bool
$c/= :: UpdateGameSession -> UpdateGameSession -> Bool
== :: UpdateGameSession -> UpdateGameSession -> Bool
$c== :: UpdateGameSession -> UpdateGameSession -> Bool
Prelude.Eq, ReadPrec [UpdateGameSession]
ReadPrec UpdateGameSession
Int -> ReadS UpdateGameSession
ReadS [UpdateGameSession]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateGameSession]
$creadListPrec :: ReadPrec [UpdateGameSession]
readPrec :: ReadPrec UpdateGameSession
$creadPrec :: ReadPrec UpdateGameSession
readList :: ReadS [UpdateGameSession]
$creadList :: ReadS [UpdateGameSession]
readsPrec :: Int -> ReadS UpdateGameSession
$creadsPrec :: Int -> ReadS UpdateGameSession
Prelude.Read, Int -> UpdateGameSession -> ShowS
[UpdateGameSession] -> ShowS
UpdateGameSession -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateGameSession] -> ShowS
$cshowList :: [UpdateGameSession] -> ShowS
show :: UpdateGameSession -> String
$cshow :: UpdateGameSession -> String
showsPrec :: Int -> UpdateGameSession -> ShowS
$cshowsPrec :: Int -> UpdateGameSession -> ShowS
Prelude.Show, forall x. Rep UpdateGameSession x -> UpdateGameSession
forall x. UpdateGameSession -> Rep UpdateGameSession x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateGameSession x -> UpdateGameSession
$cfrom :: forall x. UpdateGameSession -> Rep UpdateGameSession x
Prelude.Generic)

-- |
-- Create a value of 'UpdateGameSession' 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:
--
-- 'maximumPlayerSessionCount', 'updateGameSession_maximumPlayerSessionCount' - The maximum number of players that can be connected simultaneously to
-- the game session.
--
-- 'name', 'updateGameSession_name' - A descriptive label that is associated with a game session. Session
-- names do not need to be unique.
--
-- 'playerSessionCreationPolicy', 'updateGameSession_playerSessionCreationPolicy' - A policy that determines whether the game session is accepting new
-- players.
--
-- 'protectionPolicy', 'updateGameSession_protectionPolicy' - Game session protection policy to apply to this game session only.
--
-- -   __NoProtection__ -- The game session can be terminated during a
--     scale-down event.
--
-- -   __FullProtection__ -- If the game session is in an @ACTIVE@ status,
--     it cannot be terminated during a scale-down event.
--
-- 'gameSessionId', 'updateGameSession_gameSessionId' - A unique identifier for the game session to update.
newUpdateGameSession ::
  -- | 'gameSessionId'
  Prelude.Text ->
  UpdateGameSession
newUpdateGameSession :: Text -> UpdateGameSession
newUpdateGameSession Text
pGameSessionId_ =
  UpdateGameSession'
    { $sel:maximumPlayerSessionCount:UpdateGameSession' :: Maybe Natural
maximumPlayerSessionCount =
        forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateGameSession' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:playerSessionCreationPolicy:UpdateGameSession' :: Maybe PlayerSessionCreationPolicy
playerSessionCreationPolicy = forall a. Maybe a
Prelude.Nothing,
      $sel:protectionPolicy:UpdateGameSession' :: Maybe ProtectionPolicy
protectionPolicy = forall a. Maybe a
Prelude.Nothing,
      $sel:gameSessionId:UpdateGameSession' :: Text
gameSessionId = Text
pGameSessionId_
    }

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

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

-- | A policy that determines whether the game session is accepting new
-- players.
updateGameSession_playerSessionCreationPolicy :: Lens.Lens' UpdateGameSession (Prelude.Maybe PlayerSessionCreationPolicy)
updateGameSession_playerSessionCreationPolicy :: Lens' UpdateGameSession (Maybe PlayerSessionCreationPolicy)
updateGameSession_playerSessionCreationPolicy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGameSession' {Maybe PlayerSessionCreationPolicy
playerSessionCreationPolicy :: Maybe PlayerSessionCreationPolicy
$sel:playerSessionCreationPolicy:UpdateGameSession' :: UpdateGameSession -> Maybe PlayerSessionCreationPolicy
playerSessionCreationPolicy} -> Maybe PlayerSessionCreationPolicy
playerSessionCreationPolicy) (\s :: UpdateGameSession
s@UpdateGameSession' {} Maybe PlayerSessionCreationPolicy
a -> UpdateGameSession
s {$sel:playerSessionCreationPolicy:UpdateGameSession' :: Maybe PlayerSessionCreationPolicy
playerSessionCreationPolicy = Maybe PlayerSessionCreationPolicy
a} :: UpdateGameSession)

-- | Game session protection policy to apply to this game session only.
--
-- -   __NoProtection__ -- The game session can be terminated during a
--     scale-down event.
--
-- -   __FullProtection__ -- If the game session is in an @ACTIVE@ status,
--     it cannot be terminated during a scale-down event.
updateGameSession_protectionPolicy :: Lens.Lens' UpdateGameSession (Prelude.Maybe ProtectionPolicy)
updateGameSession_protectionPolicy :: Lens' UpdateGameSession (Maybe ProtectionPolicy)
updateGameSession_protectionPolicy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGameSession' {Maybe ProtectionPolicy
protectionPolicy :: Maybe ProtectionPolicy
$sel:protectionPolicy:UpdateGameSession' :: UpdateGameSession -> Maybe ProtectionPolicy
protectionPolicy} -> Maybe ProtectionPolicy
protectionPolicy) (\s :: UpdateGameSession
s@UpdateGameSession' {} Maybe ProtectionPolicy
a -> UpdateGameSession
s {$sel:protectionPolicy:UpdateGameSession' :: Maybe ProtectionPolicy
protectionPolicy = Maybe ProtectionPolicy
a} :: UpdateGameSession)

-- | A unique identifier for the game session to update.
updateGameSession_gameSessionId :: Lens.Lens' UpdateGameSession Prelude.Text
updateGameSession_gameSessionId :: Lens' UpdateGameSession Text
updateGameSession_gameSessionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGameSession' {Text
gameSessionId :: Text
$sel:gameSessionId:UpdateGameSession' :: UpdateGameSession -> Text
gameSessionId} -> Text
gameSessionId) (\s :: UpdateGameSession
s@UpdateGameSession' {} Text
a -> UpdateGameSession
s {$sel:gameSessionId:UpdateGameSession' :: Text
gameSessionId = Text
a} :: UpdateGameSession)

instance Core.AWSRequest UpdateGameSession where
  type
    AWSResponse UpdateGameSession =
      UpdateGameSessionResponse
  request :: (Service -> Service)
-> UpdateGameSession -> Request UpdateGameSession
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 UpdateGameSession
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateGameSession)))
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 GameSession -> Int -> UpdateGameSessionResponse
UpdateGameSessionResponse'
            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
"GameSession")
            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 UpdateGameSession where
  hashWithSalt :: Int -> UpdateGameSession -> Int
hashWithSalt Int
_salt UpdateGameSession' {Maybe Natural
Maybe Text
Maybe PlayerSessionCreationPolicy
Maybe ProtectionPolicy
Text
gameSessionId :: Text
protectionPolicy :: Maybe ProtectionPolicy
playerSessionCreationPolicy :: Maybe PlayerSessionCreationPolicy
name :: Maybe Text
maximumPlayerSessionCount :: Maybe Natural
$sel:gameSessionId:UpdateGameSession' :: UpdateGameSession -> Text
$sel:protectionPolicy:UpdateGameSession' :: UpdateGameSession -> Maybe ProtectionPolicy
$sel:playerSessionCreationPolicy:UpdateGameSession' :: UpdateGameSession -> Maybe PlayerSessionCreationPolicy
$sel:name:UpdateGameSession' :: UpdateGameSession -> Maybe Text
$sel:maximumPlayerSessionCount:UpdateGameSession' :: UpdateGameSession -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maximumPlayerSessionCount
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PlayerSessionCreationPolicy
playerSessionCreationPolicy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ProtectionPolicy
protectionPolicy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
gameSessionId

instance Prelude.NFData UpdateGameSession where
  rnf :: UpdateGameSession -> ()
rnf UpdateGameSession' {Maybe Natural
Maybe Text
Maybe PlayerSessionCreationPolicy
Maybe ProtectionPolicy
Text
gameSessionId :: Text
protectionPolicy :: Maybe ProtectionPolicy
playerSessionCreationPolicy :: Maybe PlayerSessionCreationPolicy
name :: Maybe Text
maximumPlayerSessionCount :: Maybe Natural
$sel:gameSessionId:UpdateGameSession' :: UpdateGameSession -> Text
$sel:protectionPolicy:UpdateGameSession' :: UpdateGameSession -> Maybe ProtectionPolicy
$sel:playerSessionCreationPolicy:UpdateGameSession' :: UpdateGameSession -> Maybe PlayerSessionCreationPolicy
$sel:name:UpdateGameSession' :: UpdateGameSession -> Maybe Text
$sel:maximumPlayerSessionCount:UpdateGameSession' :: UpdateGameSession -> Maybe Natural
..} =
    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 Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PlayerSessionCreationPolicy
playerSessionCreationPolicy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ProtectionPolicy
protectionPolicy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
gameSessionId

instance Data.ToHeaders UpdateGameSession where
  toHeaders :: UpdateGameSession -> 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.UpdateGameSession" :: 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 UpdateGameSession where
  toJSON :: UpdateGameSession -> Value
toJSON UpdateGameSession' {Maybe Natural
Maybe Text
Maybe PlayerSessionCreationPolicy
Maybe ProtectionPolicy
Text
gameSessionId :: Text
protectionPolicy :: Maybe ProtectionPolicy
playerSessionCreationPolicy :: Maybe PlayerSessionCreationPolicy
name :: Maybe Text
maximumPlayerSessionCount :: Maybe Natural
$sel:gameSessionId:UpdateGameSession' :: UpdateGameSession -> Text
$sel:protectionPolicy:UpdateGameSession' :: UpdateGameSession -> Maybe ProtectionPolicy
$sel:playerSessionCreationPolicy:UpdateGameSession' :: UpdateGameSession -> Maybe PlayerSessionCreationPolicy
$sel:name:UpdateGameSession' :: UpdateGameSession -> Maybe Text
$sel:maximumPlayerSessionCount:UpdateGameSession' :: UpdateGameSession -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"MaximumPlayerSessionCount" 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
maximumPlayerSessionCount,
            (Key
"Name" 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
name,
            (Key
"PlayerSessionCreationPolicy" 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 PlayerSessionCreationPolicy
playerSessionCreationPolicy,
            (Key
"ProtectionPolicy" 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 ProtectionPolicy
protectionPolicy,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"GameSessionId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
gameSessionId)
          ]
      )

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

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

-- | /See:/ 'newUpdateGameSessionResponse' smart constructor.
data UpdateGameSessionResponse = UpdateGameSessionResponse'
  { -- | The updated game session properties.
    UpdateGameSessionResponse -> Maybe GameSession
gameSession :: Prelude.Maybe GameSession,
    -- | The response's http status code.
    UpdateGameSessionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateGameSessionResponse -> UpdateGameSessionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateGameSessionResponse -> UpdateGameSessionResponse -> Bool
$c/= :: UpdateGameSessionResponse -> UpdateGameSessionResponse -> Bool
== :: UpdateGameSessionResponse -> UpdateGameSessionResponse -> Bool
$c== :: UpdateGameSessionResponse -> UpdateGameSessionResponse -> Bool
Prelude.Eq, ReadPrec [UpdateGameSessionResponse]
ReadPrec UpdateGameSessionResponse
Int -> ReadS UpdateGameSessionResponse
ReadS [UpdateGameSessionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateGameSessionResponse]
$creadListPrec :: ReadPrec [UpdateGameSessionResponse]
readPrec :: ReadPrec UpdateGameSessionResponse
$creadPrec :: ReadPrec UpdateGameSessionResponse
readList :: ReadS [UpdateGameSessionResponse]
$creadList :: ReadS [UpdateGameSessionResponse]
readsPrec :: Int -> ReadS UpdateGameSessionResponse
$creadsPrec :: Int -> ReadS UpdateGameSessionResponse
Prelude.Read, Int -> UpdateGameSessionResponse -> ShowS
[UpdateGameSessionResponse] -> ShowS
UpdateGameSessionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateGameSessionResponse] -> ShowS
$cshowList :: [UpdateGameSessionResponse] -> ShowS
show :: UpdateGameSessionResponse -> String
$cshow :: UpdateGameSessionResponse -> String
showsPrec :: Int -> UpdateGameSessionResponse -> ShowS
$cshowsPrec :: Int -> UpdateGameSessionResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateGameSessionResponse x -> UpdateGameSessionResponse
forall x.
UpdateGameSessionResponse -> Rep UpdateGameSessionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateGameSessionResponse x -> UpdateGameSessionResponse
$cfrom :: forall x.
UpdateGameSessionResponse -> Rep UpdateGameSessionResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateGameSessionResponse' 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:
--
-- 'gameSession', 'updateGameSessionResponse_gameSession' - The updated game session properties.
--
-- 'httpStatus', 'updateGameSessionResponse_httpStatus' - The response's http status code.
newUpdateGameSessionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateGameSessionResponse
newUpdateGameSessionResponse :: Int -> UpdateGameSessionResponse
newUpdateGameSessionResponse Int
pHttpStatus_ =
  UpdateGameSessionResponse'
    { $sel:gameSession:UpdateGameSessionResponse' :: Maybe GameSession
gameSession =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateGameSessionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The updated game session properties.
updateGameSessionResponse_gameSession :: Lens.Lens' UpdateGameSessionResponse (Prelude.Maybe GameSession)
updateGameSessionResponse_gameSession :: Lens' UpdateGameSessionResponse (Maybe GameSession)
updateGameSessionResponse_gameSession = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGameSessionResponse' {Maybe GameSession
gameSession :: Maybe GameSession
$sel:gameSession:UpdateGameSessionResponse' :: UpdateGameSessionResponse -> Maybe GameSession
gameSession} -> Maybe GameSession
gameSession) (\s :: UpdateGameSessionResponse
s@UpdateGameSessionResponse' {} Maybe GameSession
a -> UpdateGameSessionResponse
s {$sel:gameSession:UpdateGameSessionResponse' :: Maybe GameSession
gameSession = Maybe GameSession
a} :: UpdateGameSessionResponse)

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

instance Prelude.NFData UpdateGameSessionResponse where
  rnf :: UpdateGameSessionResponse -> ()
rnf UpdateGameSessionResponse' {Int
Maybe GameSession
httpStatus :: Int
gameSession :: Maybe GameSession
$sel:httpStatus:UpdateGameSessionResponse' :: UpdateGameSessionResponse -> Int
$sel:gameSession:UpdateGameSessionResponse' :: UpdateGameSessionResponse -> Maybe GameSession
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe GameSession
gameSession
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus