{-# 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.Synthetics.GetGroup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns information about one group. Groups are a global resource, so
-- you can use this operation from any Region.
module Amazonka.Synthetics.GetGroup
  ( -- * Creating a Request
    GetGroup (..),
    newGetGroup,

    -- * Request Lenses
    getGroup_groupIdentifier,

    -- * Destructuring the Response
    GetGroupResponse (..),
    newGetGroupResponse,

    -- * Response Lenses
    getGroupResponse_group,
    getGroupResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.Synthetics.Types

-- | /See:/ 'newGetGroup' smart constructor.
data GetGroup = GetGroup'
  { -- | Specifies the group to return information for. You can specify the group
    -- name, the ARN, or the group ID as the @GroupIdentifier@.
    GetGroup -> Text
groupIdentifier :: Prelude.Text
  }
  deriving (GetGroup -> GetGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetGroup -> GetGroup -> Bool
$c/= :: GetGroup -> GetGroup -> Bool
== :: GetGroup -> GetGroup -> Bool
$c== :: GetGroup -> GetGroup -> Bool
Prelude.Eq, ReadPrec [GetGroup]
ReadPrec GetGroup
Int -> ReadS GetGroup
ReadS [GetGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetGroup]
$creadListPrec :: ReadPrec [GetGroup]
readPrec :: ReadPrec GetGroup
$creadPrec :: ReadPrec GetGroup
readList :: ReadS [GetGroup]
$creadList :: ReadS [GetGroup]
readsPrec :: Int -> ReadS GetGroup
$creadsPrec :: Int -> ReadS GetGroup
Prelude.Read, Int -> GetGroup -> ShowS
[GetGroup] -> ShowS
GetGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetGroup] -> ShowS
$cshowList :: [GetGroup] -> ShowS
show :: GetGroup -> String
$cshow :: GetGroup -> String
showsPrec :: Int -> GetGroup -> ShowS
$cshowsPrec :: Int -> GetGroup -> ShowS
Prelude.Show, forall x. Rep GetGroup x -> GetGroup
forall x. GetGroup -> Rep GetGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetGroup x -> GetGroup
$cfrom :: forall x. GetGroup -> Rep GetGroup x
Prelude.Generic)

-- |
-- Create a value of 'GetGroup' 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:
--
-- 'groupIdentifier', 'getGroup_groupIdentifier' - Specifies the group to return information for. You can specify the group
-- name, the ARN, or the group ID as the @GroupIdentifier@.
newGetGroup ::
  -- | 'groupIdentifier'
  Prelude.Text ->
  GetGroup
newGetGroup :: Text -> GetGroup
newGetGroup Text
pGroupIdentifier_ =
  GetGroup' {$sel:groupIdentifier:GetGroup' :: Text
groupIdentifier = Text
pGroupIdentifier_}

-- | Specifies the group to return information for. You can specify the group
-- name, the ARN, or the group ID as the @GroupIdentifier@.
getGroup_groupIdentifier :: Lens.Lens' GetGroup Prelude.Text
getGroup_groupIdentifier :: Lens' GetGroup Text
getGroup_groupIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGroup' {Text
groupIdentifier :: Text
$sel:groupIdentifier:GetGroup' :: GetGroup -> Text
groupIdentifier} -> Text
groupIdentifier) (\s :: GetGroup
s@GetGroup' {} Text
a -> GetGroup
s {$sel:groupIdentifier:GetGroup' :: Text
groupIdentifier = Text
a} :: GetGroup)

instance Core.AWSRequest GetGroup where
  type AWSResponse GetGroup = GetGroupResponse
  request :: (Service -> Service) -> GetGroup -> Request GetGroup
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetGroup
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetGroup)))
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 Group -> Int -> GetGroupResponse
GetGroupResponse'
            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
"Group")
            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 GetGroup where
  hashWithSalt :: Int -> GetGroup -> Int
hashWithSalt Int
_salt GetGroup' {Text
groupIdentifier :: Text
$sel:groupIdentifier:GetGroup' :: GetGroup -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
groupIdentifier

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

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

instance Data.ToPath GetGroup where
  toPath :: GetGroup -> ByteString
toPath GetGroup' {Text
groupIdentifier :: Text
$sel:groupIdentifier:GetGroup' :: GetGroup -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/group/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
groupIdentifier]

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

-- | /See:/ 'newGetGroupResponse' smart constructor.
data GetGroupResponse = GetGroupResponse'
  { -- | A structure that contains information about the group.
    GetGroupResponse -> Maybe Group
group' :: Prelude.Maybe Group,
    -- | The response's http status code.
    GetGroupResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetGroupResponse -> GetGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetGroupResponse -> GetGroupResponse -> Bool
$c/= :: GetGroupResponse -> GetGroupResponse -> Bool
== :: GetGroupResponse -> GetGroupResponse -> Bool
$c== :: GetGroupResponse -> GetGroupResponse -> Bool
Prelude.Eq, ReadPrec [GetGroupResponse]
ReadPrec GetGroupResponse
Int -> ReadS GetGroupResponse
ReadS [GetGroupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetGroupResponse]
$creadListPrec :: ReadPrec [GetGroupResponse]
readPrec :: ReadPrec GetGroupResponse
$creadPrec :: ReadPrec GetGroupResponse
readList :: ReadS [GetGroupResponse]
$creadList :: ReadS [GetGroupResponse]
readsPrec :: Int -> ReadS GetGroupResponse
$creadsPrec :: Int -> ReadS GetGroupResponse
Prelude.Read, Int -> GetGroupResponse -> ShowS
[GetGroupResponse] -> ShowS
GetGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetGroupResponse] -> ShowS
$cshowList :: [GetGroupResponse] -> ShowS
show :: GetGroupResponse -> String
$cshow :: GetGroupResponse -> String
showsPrec :: Int -> GetGroupResponse -> ShowS
$cshowsPrec :: Int -> GetGroupResponse -> ShowS
Prelude.Show, forall x. Rep GetGroupResponse x -> GetGroupResponse
forall x. GetGroupResponse -> Rep GetGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetGroupResponse x -> GetGroupResponse
$cfrom :: forall x. GetGroupResponse -> Rep GetGroupResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetGroupResponse' 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:
--
-- 'group'', 'getGroupResponse_group' - A structure that contains information about the group.
--
-- 'httpStatus', 'getGroupResponse_httpStatus' - The response's http status code.
newGetGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetGroupResponse
newGetGroupResponse :: Int -> GetGroupResponse
newGetGroupResponse Int
pHttpStatus_ =
  GetGroupResponse'
    { $sel:group':GetGroupResponse' :: Maybe Group
group' = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A structure that contains information about the group.
getGroupResponse_group :: Lens.Lens' GetGroupResponse (Prelude.Maybe Group)
getGroupResponse_group :: Lens' GetGroupResponse (Maybe Group)
getGroupResponse_group = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGroupResponse' {Maybe Group
group' :: Maybe Group
$sel:group':GetGroupResponse' :: GetGroupResponse -> Maybe Group
group'} -> Maybe Group
group') (\s :: GetGroupResponse
s@GetGroupResponse' {} Maybe Group
a -> GetGroupResponse
s {$sel:group':GetGroupResponse' :: Maybe Group
group' = Maybe Group
a} :: GetGroupResponse)

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

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