{-# 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.CognitoIdentityProvider.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)
--
-- Gets a group.
--
-- Calling this action requires developer credentials.
module Amazonka.CognitoIdentityProvider.GetGroup
  ( -- * Creating a Request
    GetGroup (..),
    newGetGroup,

    -- * Request Lenses
    getGroup_groupName,
    getGroup_userPoolId,

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

    -- * Response Lenses
    getGroupResponse_group,
    getGroupResponse_httpStatus,
  )
where

import Amazonka.CognitoIdentityProvider.Types
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

-- | /See:/ 'newGetGroup' smart constructor.
data GetGroup = GetGroup'
  { -- | The name of the group.
    GetGroup -> Text
groupName :: Prelude.Text,
    -- | The user pool ID for the user pool.
    GetGroup -> Text
userPoolId :: 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:
--
-- 'groupName', 'getGroup_groupName' - The name of the group.
--
-- 'userPoolId', 'getGroup_userPoolId' - The user pool ID for the user pool.
newGetGroup ::
  -- | 'groupName'
  Prelude.Text ->
  -- | 'userPoolId'
  Prelude.Text ->
  GetGroup
newGetGroup :: Text -> Text -> GetGroup
newGetGroup Text
pGroupName_ Text
pUserPoolId_ =
  GetGroup'
    { $sel:groupName:GetGroup' :: Text
groupName = Text
pGroupName_,
      $sel:userPoolId:GetGroup' :: Text
userPoolId = Text
pUserPoolId_
    }

-- | The name of the group.
getGroup_groupName :: Lens.Lens' GetGroup Prelude.Text
getGroup_groupName :: Lens' GetGroup Text
getGroup_groupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGroup' {Text
groupName :: Text
$sel:groupName:GetGroup' :: GetGroup -> Text
groupName} -> Text
groupName) (\s :: GetGroup
s@GetGroup' {} Text
a -> GetGroup
s {$sel:groupName:GetGroup' :: Text
groupName = Text
a} :: GetGroup)

-- | The user pool ID for the user pool.
getGroup_userPoolId :: Lens.Lens' GetGroup Prelude.Text
getGroup_userPoolId :: Lens' GetGroup Text
getGroup_userPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGroup' {Text
userPoolId :: Text
$sel:userPoolId:GetGroup' :: GetGroup -> Text
userPoolId} -> Text
userPoolId) (\s :: GetGroup
s@GetGroup' {} Text
a -> GetGroup
s {$sel:userPoolId:GetGroup' :: Text
userPoolId = 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, ToJSON a) => Service -> a -> Request a
Request.postJSON (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 GroupType -> 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
userPoolId :: Text
groupName :: Text
$sel:userPoolId:GetGroup' :: GetGroup -> Text
$sel:groupName:GetGroup' :: GetGroup -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
groupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userPoolId

instance Prelude.NFData GetGroup where
  rnf :: GetGroup -> ()
rnf GetGroup' {Text
userPoolId :: Text
groupName :: Text
$sel:userPoolId:GetGroup' :: GetGroup -> Text
$sel:groupName:GetGroup' :: GetGroup -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
groupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
userPoolId

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
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AWSCognitoIdentityProviderService.GetGroup" ::
                          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 GetGroup where
  toJSON :: GetGroup -> Value
toJSON GetGroup' {Text
userPoolId :: Text
groupName :: Text
$sel:userPoolId:GetGroup' :: GetGroup -> Text
$sel:groupName:GetGroup' :: GetGroup -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"GroupName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
groupName),
            forall a. a -> Maybe a
Prelude.Just (Key
"UserPoolId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
userPoolId)
          ]
      )

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

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'
  { -- | The group object for the group.
    GetGroupResponse -> Maybe GroupType
group' :: Prelude.Maybe GroupType,
    -- | 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' - The group object for 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 GroupType
group' = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The group object for the group.
getGroupResponse_group :: Lens.Lens' GetGroupResponse (Prelude.Maybe GroupType)
getGroupResponse_group :: Lens' GetGroupResponse (Maybe GroupType)
getGroupResponse_group = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGroupResponse' {Maybe GroupType
group' :: Maybe GroupType
$sel:group':GetGroupResponse' :: GetGroupResponse -> Maybe GroupType
group'} -> Maybe GroupType
group') (\s :: GetGroupResponse
s@GetGroupResponse' {} Maybe GroupType
a -> GetGroupResponse
s {$sel:group':GetGroupResponse' :: Maybe GroupType
group' = Maybe GroupType
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 GroupType
httpStatus :: Int
group' :: Maybe GroupType
$sel:httpStatus:GetGroupResponse' :: GetGroupResponse -> Int
$sel:group':GetGroupResponse' :: GetGroupResponse -> Maybe GroupType
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe GroupType
group'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus