{-# 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.DescribeGameServerGroup
-- 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 on a game server group. This operation returns
-- only properties related to GameLift FleetIQ. To view or update
-- properties for the corresponding Auto Scaling group, such as launch
-- template, auto scaling policies, and maximum\/minimum group size, access
-- the Auto Scaling group directly.
--
-- To get attributes for a game server group, provide a group name or ARN
-- value. If successful, a @GameServerGroup@ object is returned.
--
-- __Learn more__
--
-- <https://docs.aws.amazon.com/gamelift/latest/fleetiqguide/gsg-intro.html GameLift FleetIQ Guide>
module Amazonka.GameLift.DescribeGameServerGroup
  ( -- * Creating a Request
    DescribeGameServerGroup (..),
    newDescribeGameServerGroup,

    -- * Request Lenses
    describeGameServerGroup_gameServerGroupName,

    -- * Destructuring the Response
    DescribeGameServerGroupResponse (..),
    newDescribeGameServerGroupResponse,

    -- * Response Lenses
    describeGameServerGroupResponse_gameServerGroup,
    describeGameServerGroupResponse_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:/ 'newDescribeGameServerGroup' smart constructor.
data DescribeGameServerGroup = DescribeGameServerGroup'
  { -- | A unique identifier for the game server group. Use either the name or
    -- ARN value.
    DescribeGameServerGroup -> Text
gameServerGroupName :: Prelude.Text
  }
  deriving (DescribeGameServerGroup -> DescribeGameServerGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeGameServerGroup -> DescribeGameServerGroup -> Bool
$c/= :: DescribeGameServerGroup -> DescribeGameServerGroup -> Bool
== :: DescribeGameServerGroup -> DescribeGameServerGroup -> Bool
$c== :: DescribeGameServerGroup -> DescribeGameServerGroup -> Bool
Prelude.Eq, ReadPrec [DescribeGameServerGroup]
ReadPrec DescribeGameServerGroup
Int -> ReadS DescribeGameServerGroup
ReadS [DescribeGameServerGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeGameServerGroup]
$creadListPrec :: ReadPrec [DescribeGameServerGroup]
readPrec :: ReadPrec DescribeGameServerGroup
$creadPrec :: ReadPrec DescribeGameServerGroup
readList :: ReadS [DescribeGameServerGroup]
$creadList :: ReadS [DescribeGameServerGroup]
readsPrec :: Int -> ReadS DescribeGameServerGroup
$creadsPrec :: Int -> ReadS DescribeGameServerGroup
Prelude.Read, Int -> DescribeGameServerGroup -> ShowS
[DescribeGameServerGroup] -> ShowS
DescribeGameServerGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeGameServerGroup] -> ShowS
$cshowList :: [DescribeGameServerGroup] -> ShowS
show :: DescribeGameServerGroup -> String
$cshow :: DescribeGameServerGroup -> String
showsPrec :: Int -> DescribeGameServerGroup -> ShowS
$cshowsPrec :: Int -> DescribeGameServerGroup -> ShowS
Prelude.Show, forall x. Rep DescribeGameServerGroup x -> DescribeGameServerGroup
forall x. DescribeGameServerGroup -> Rep DescribeGameServerGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeGameServerGroup x -> DescribeGameServerGroup
$cfrom :: forall x. DescribeGameServerGroup -> Rep DescribeGameServerGroup x
Prelude.Generic)

-- |
-- Create a value of 'DescribeGameServerGroup' 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', 'describeGameServerGroup_gameServerGroupName' - A unique identifier for the game server group. Use either the name or
-- ARN value.
newDescribeGameServerGroup ::
  -- | 'gameServerGroupName'
  Prelude.Text ->
  DescribeGameServerGroup
newDescribeGameServerGroup :: Text -> DescribeGameServerGroup
newDescribeGameServerGroup Text
pGameServerGroupName_ =
  DescribeGameServerGroup'
    { $sel:gameServerGroupName:DescribeGameServerGroup' :: Text
gameServerGroupName =
        Text
pGameServerGroupName_
    }

-- | A unique identifier for the game server group. Use either the name or
-- ARN value.
describeGameServerGroup_gameServerGroupName :: Lens.Lens' DescribeGameServerGroup Prelude.Text
describeGameServerGroup_gameServerGroupName :: Lens' DescribeGameServerGroup Text
describeGameServerGroup_gameServerGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeGameServerGroup' {Text
gameServerGroupName :: Text
$sel:gameServerGroupName:DescribeGameServerGroup' :: DescribeGameServerGroup -> Text
gameServerGroupName} -> Text
gameServerGroupName) (\s :: DescribeGameServerGroup
s@DescribeGameServerGroup' {} Text
a -> DescribeGameServerGroup
s {$sel:gameServerGroupName:DescribeGameServerGroup' :: Text
gameServerGroupName = Text
a} :: DescribeGameServerGroup)

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

instance Prelude.NFData DescribeGameServerGroup where
  rnf :: DescribeGameServerGroup -> ()
rnf DescribeGameServerGroup' {Text
gameServerGroupName :: Text
$sel:gameServerGroupName:DescribeGameServerGroup' :: DescribeGameServerGroup -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
gameServerGroupName

instance Data.ToHeaders DescribeGameServerGroup where
  toHeaders :: DescribeGameServerGroup -> 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.DescribeGameServerGroup" ::
                          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 DescribeGameServerGroup where
  toJSON :: DescribeGameServerGroup -> Value
toJSON DescribeGameServerGroup' {Text
gameServerGroupName :: Text
$sel:gameServerGroupName:DescribeGameServerGroup' :: DescribeGameServerGroup -> 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)
          ]
      )

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

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

-- | /See:/ 'newDescribeGameServerGroupResponse' smart constructor.
data DescribeGameServerGroupResponse = DescribeGameServerGroupResponse'
  { -- | An object with the property settings for the requested game server group
    -- resource.
    DescribeGameServerGroupResponse -> Maybe GameServerGroup
gameServerGroup :: Prelude.Maybe GameServerGroup,
    -- | The response's http status code.
    DescribeGameServerGroupResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeGameServerGroupResponse
-> DescribeGameServerGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeGameServerGroupResponse
-> DescribeGameServerGroupResponse -> Bool
$c/= :: DescribeGameServerGroupResponse
-> DescribeGameServerGroupResponse -> Bool
== :: DescribeGameServerGroupResponse
-> DescribeGameServerGroupResponse -> Bool
$c== :: DescribeGameServerGroupResponse
-> DescribeGameServerGroupResponse -> Bool
Prelude.Eq, ReadPrec [DescribeGameServerGroupResponse]
ReadPrec DescribeGameServerGroupResponse
Int -> ReadS DescribeGameServerGroupResponse
ReadS [DescribeGameServerGroupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeGameServerGroupResponse]
$creadListPrec :: ReadPrec [DescribeGameServerGroupResponse]
readPrec :: ReadPrec DescribeGameServerGroupResponse
$creadPrec :: ReadPrec DescribeGameServerGroupResponse
readList :: ReadS [DescribeGameServerGroupResponse]
$creadList :: ReadS [DescribeGameServerGroupResponse]
readsPrec :: Int -> ReadS DescribeGameServerGroupResponse
$creadsPrec :: Int -> ReadS DescribeGameServerGroupResponse
Prelude.Read, Int -> DescribeGameServerGroupResponse -> ShowS
[DescribeGameServerGroupResponse] -> ShowS
DescribeGameServerGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeGameServerGroupResponse] -> ShowS
$cshowList :: [DescribeGameServerGroupResponse] -> ShowS
show :: DescribeGameServerGroupResponse -> String
$cshow :: DescribeGameServerGroupResponse -> String
showsPrec :: Int -> DescribeGameServerGroupResponse -> ShowS
$cshowsPrec :: Int -> DescribeGameServerGroupResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeGameServerGroupResponse x
-> DescribeGameServerGroupResponse
forall x.
DescribeGameServerGroupResponse
-> Rep DescribeGameServerGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeGameServerGroupResponse x
-> DescribeGameServerGroupResponse
$cfrom :: forall x.
DescribeGameServerGroupResponse
-> Rep DescribeGameServerGroupResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeGameServerGroupResponse' 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:
--
-- 'gameServerGroup', 'describeGameServerGroupResponse_gameServerGroup' - An object with the property settings for the requested game server group
-- resource.
--
-- 'httpStatus', 'describeGameServerGroupResponse_httpStatus' - The response's http status code.
newDescribeGameServerGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeGameServerGroupResponse
newDescribeGameServerGroupResponse :: Int -> DescribeGameServerGroupResponse
newDescribeGameServerGroupResponse Int
pHttpStatus_ =
  DescribeGameServerGroupResponse'
    { $sel:gameServerGroup:DescribeGameServerGroupResponse' :: Maybe GameServerGroup
gameServerGroup =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeGameServerGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An object with the property settings for the requested game server group
-- resource.
describeGameServerGroupResponse_gameServerGroup :: Lens.Lens' DescribeGameServerGroupResponse (Prelude.Maybe GameServerGroup)
describeGameServerGroupResponse_gameServerGroup :: Lens' DescribeGameServerGroupResponse (Maybe GameServerGroup)
describeGameServerGroupResponse_gameServerGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeGameServerGroupResponse' {Maybe GameServerGroup
gameServerGroup :: Maybe GameServerGroup
$sel:gameServerGroup:DescribeGameServerGroupResponse' :: DescribeGameServerGroupResponse -> Maybe GameServerGroup
gameServerGroup} -> Maybe GameServerGroup
gameServerGroup) (\s :: DescribeGameServerGroupResponse
s@DescribeGameServerGroupResponse' {} Maybe GameServerGroup
a -> DescribeGameServerGroupResponse
s {$sel:gameServerGroup:DescribeGameServerGroupResponse' :: Maybe GameServerGroup
gameServerGroup = Maybe GameServerGroup
a} :: DescribeGameServerGroupResponse)

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

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