{-# 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.DescribeGameServer
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- __This operation is used with the GameLift FleetIQ solution and game
-- server groups.__
--
-- Retrieves information for a registered game server. Information includes
-- game server status, health check info, and the instance that the game
-- server is running on.
--
-- To retrieve game server information, specify the game server ID. If
-- successful, the requested game server object is returned.
--
-- __Learn more__
--
-- <https://docs.aws.amazon.com/gamelift/latest/fleetiqguide/gsg-intro.html GameLift FleetIQ Guide>
module Amazonka.GameLift.DescribeGameServer
  ( -- * Creating a Request
    DescribeGameServer (..),
    newDescribeGameServer,

    -- * Request Lenses
    describeGameServer_gameServerGroupName,
    describeGameServer_gameServerId,

    -- * Destructuring the Response
    DescribeGameServerResponse (..),
    newDescribeGameServerResponse,

    -- * Response Lenses
    describeGameServerResponse_gameServer,
    describeGameServerResponse_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:/ 'newDescribeGameServer' smart constructor.
data DescribeGameServer = DescribeGameServer'
  { -- | A unique identifier for the game server group where the game server is
    -- running.
    DescribeGameServer -> Text
gameServerGroupName :: Prelude.Text,
    -- | A custom string that uniquely identifies the game server information to
    -- be retrieved.
    DescribeGameServer -> Text
gameServerId :: Prelude.Text
  }
  deriving (DescribeGameServer -> DescribeGameServer -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeGameServer -> DescribeGameServer -> Bool
$c/= :: DescribeGameServer -> DescribeGameServer -> Bool
== :: DescribeGameServer -> DescribeGameServer -> Bool
$c== :: DescribeGameServer -> DescribeGameServer -> Bool
Prelude.Eq, ReadPrec [DescribeGameServer]
ReadPrec DescribeGameServer
Int -> ReadS DescribeGameServer
ReadS [DescribeGameServer]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeGameServer]
$creadListPrec :: ReadPrec [DescribeGameServer]
readPrec :: ReadPrec DescribeGameServer
$creadPrec :: ReadPrec DescribeGameServer
readList :: ReadS [DescribeGameServer]
$creadList :: ReadS [DescribeGameServer]
readsPrec :: Int -> ReadS DescribeGameServer
$creadsPrec :: Int -> ReadS DescribeGameServer
Prelude.Read, Int -> DescribeGameServer -> ShowS
[DescribeGameServer] -> ShowS
DescribeGameServer -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeGameServer] -> ShowS
$cshowList :: [DescribeGameServer] -> ShowS
show :: DescribeGameServer -> String
$cshow :: DescribeGameServer -> String
showsPrec :: Int -> DescribeGameServer -> ShowS
$cshowsPrec :: Int -> DescribeGameServer -> ShowS
Prelude.Show, forall x. Rep DescribeGameServer x -> DescribeGameServer
forall x. DescribeGameServer -> Rep DescribeGameServer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeGameServer x -> DescribeGameServer
$cfrom :: forall x. DescribeGameServer -> Rep DescribeGameServer x
Prelude.Generic)

-- |
-- Create a value of 'DescribeGameServer' 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:
--
-- 'gameServerGroupName', 'describeGameServer_gameServerGroupName' - A unique identifier for the game server group where the game server is
-- running.
--
-- 'gameServerId', 'describeGameServer_gameServerId' - A custom string that uniquely identifies the game server information to
-- be retrieved.
newDescribeGameServer ::
  -- | 'gameServerGroupName'
  Prelude.Text ->
  -- | 'gameServerId'
  Prelude.Text ->
  DescribeGameServer
newDescribeGameServer :: Text -> Text -> DescribeGameServer
newDescribeGameServer
  Text
pGameServerGroupName_
  Text
pGameServerId_ =
    DescribeGameServer'
      { $sel:gameServerGroupName:DescribeGameServer' :: Text
gameServerGroupName =
          Text
pGameServerGroupName_,
        $sel:gameServerId:DescribeGameServer' :: Text
gameServerId = Text
pGameServerId_
      }

-- | A unique identifier for the game server group where the game server is
-- running.
describeGameServer_gameServerGroupName :: Lens.Lens' DescribeGameServer Prelude.Text
describeGameServer_gameServerGroupName :: Lens' DescribeGameServer Text
describeGameServer_gameServerGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeGameServer' {Text
gameServerGroupName :: Text
$sel:gameServerGroupName:DescribeGameServer' :: DescribeGameServer -> Text
gameServerGroupName} -> Text
gameServerGroupName) (\s :: DescribeGameServer
s@DescribeGameServer' {} Text
a -> DescribeGameServer
s {$sel:gameServerGroupName:DescribeGameServer' :: Text
gameServerGroupName = Text
a} :: DescribeGameServer)

-- | A custom string that uniquely identifies the game server information to
-- be retrieved.
describeGameServer_gameServerId :: Lens.Lens' DescribeGameServer Prelude.Text
describeGameServer_gameServerId :: Lens' DescribeGameServer Text
describeGameServer_gameServerId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeGameServer' {Text
gameServerId :: Text
$sel:gameServerId:DescribeGameServer' :: DescribeGameServer -> Text
gameServerId} -> Text
gameServerId) (\s :: DescribeGameServer
s@DescribeGameServer' {} Text
a -> DescribeGameServer
s {$sel:gameServerId:DescribeGameServer' :: Text
gameServerId = Text
a} :: DescribeGameServer)

instance Core.AWSRequest DescribeGameServer where
  type
    AWSResponse DescribeGameServer =
      DescribeGameServerResponse
  request :: (Service -> Service)
-> DescribeGameServer -> Request DescribeGameServer
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 DescribeGameServer
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeGameServer)))
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 GameServer -> Int -> DescribeGameServerResponse
DescribeGameServerResponse'
            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
"GameServer")
            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 DescribeGameServer where
  hashWithSalt :: Int -> DescribeGameServer -> Int
hashWithSalt Int
_salt DescribeGameServer' {Text
gameServerId :: Text
gameServerGroupName :: Text
$sel:gameServerId:DescribeGameServer' :: DescribeGameServer -> Text
$sel:gameServerGroupName:DescribeGameServer' :: DescribeGameServer -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
gameServerGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
gameServerId

instance Prelude.NFData DescribeGameServer where
  rnf :: DescribeGameServer -> ()
rnf DescribeGameServer' {Text
gameServerId :: Text
gameServerGroupName :: Text
$sel:gameServerId:DescribeGameServer' :: DescribeGameServer -> Text
$sel:gameServerGroupName:DescribeGameServer' :: DescribeGameServer -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
gameServerGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
gameServerId

instance Data.ToHeaders DescribeGameServer where
  toHeaders :: DescribeGameServer -> 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.DescribeGameServer" ::
                          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 DescribeGameServer where
  toJSON :: DescribeGameServer -> Value
toJSON DescribeGameServer' {Text
gameServerId :: Text
gameServerGroupName :: Text
$sel:gameServerId:DescribeGameServer' :: DescribeGameServer -> Text
$sel:gameServerGroupName:DescribeGameServer' :: DescribeGameServer -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"GameServerGroupName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
gameServerGroupName),
            forall a. a -> Maybe a
Prelude.Just (Key
"GameServerId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
gameServerId)
          ]
      )

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

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

-- | /See:/ 'newDescribeGameServerResponse' smart constructor.
data DescribeGameServerResponse = DescribeGameServerResponse'
  { -- | Object that describes the requested game server.
    DescribeGameServerResponse -> Maybe GameServer
gameServer :: Prelude.Maybe GameServer,
    -- | The response's http status code.
    DescribeGameServerResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeGameServerResponse -> DescribeGameServerResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeGameServerResponse -> DescribeGameServerResponse -> Bool
$c/= :: DescribeGameServerResponse -> DescribeGameServerResponse -> Bool
== :: DescribeGameServerResponse -> DescribeGameServerResponse -> Bool
$c== :: DescribeGameServerResponse -> DescribeGameServerResponse -> Bool
Prelude.Eq, ReadPrec [DescribeGameServerResponse]
ReadPrec DescribeGameServerResponse
Int -> ReadS DescribeGameServerResponse
ReadS [DescribeGameServerResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeGameServerResponse]
$creadListPrec :: ReadPrec [DescribeGameServerResponse]
readPrec :: ReadPrec DescribeGameServerResponse
$creadPrec :: ReadPrec DescribeGameServerResponse
readList :: ReadS [DescribeGameServerResponse]
$creadList :: ReadS [DescribeGameServerResponse]
readsPrec :: Int -> ReadS DescribeGameServerResponse
$creadsPrec :: Int -> ReadS DescribeGameServerResponse
Prelude.Read, Int -> DescribeGameServerResponse -> ShowS
[DescribeGameServerResponse] -> ShowS
DescribeGameServerResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeGameServerResponse] -> ShowS
$cshowList :: [DescribeGameServerResponse] -> ShowS
show :: DescribeGameServerResponse -> String
$cshow :: DescribeGameServerResponse -> String
showsPrec :: Int -> DescribeGameServerResponse -> ShowS
$cshowsPrec :: Int -> DescribeGameServerResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeGameServerResponse x -> DescribeGameServerResponse
forall x.
DescribeGameServerResponse -> Rep DescribeGameServerResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeGameServerResponse x -> DescribeGameServerResponse
$cfrom :: forall x.
DescribeGameServerResponse -> Rep DescribeGameServerResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeGameServerResponse' 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:
--
-- 'gameServer', 'describeGameServerResponse_gameServer' - Object that describes the requested game server.
--
-- 'httpStatus', 'describeGameServerResponse_httpStatus' - The response's http status code.
newDescribeGameServerResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeGameServerResponse
newDescribeGameServerResponse :: Int -> DescribeGameServerResponse
newDescribeGameServerResponse Int
pHttpStatus_ =
  DescribeGameServerResponse'
    { $sel:gameServer:DescribeGameServerResponse' :: Maybe GameServer
gameServer =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeGameServerResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Object that describes the requested game server.
describeGameServerResponse_gameServer :: Lens.Lens' DescribeGameServerResponse (Prelude.Maybe GameServer)
describeGameServerResponse_gameServer :: Lens' DescribeGameServerResponse (Maybe GameServer)
describeGameServerResponse_gameServer = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeGameServerResponse' {Maybe GameServer
gameServer :: Maybe GameServer
$sel:gameServer:DescribeGameServerResponse' :: DescribeGameServerResponse -> Maybe GameServer
gameServer} -> Maybe GameServer
gameServer) (\s :: DescribeGameServerResponse
s@DescribeGameServerResponse' {} Maybe GameServer
a -> DescribeGameServerResponse
s {$sel:gameServer:DescribeGameServerResponse' :: Maybe GameServer
gameServer = Maybe GameServer
a} :: DescribeGameServerResponse)

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

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