{-# 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.IdentityStore.DescribeGroup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves the group metadata and attributes from @GroupId@ in an
-- identity store.
module Amazonka.IdentityStore.DescribeGroup
  ( -- * Creating a Request
    DescribeGroup (..),
    newDescribeGroup,

    -- * Request Lenses
    describeGroup_identityStoreId,
    describeGroup_groupId,

    -- * Destructuring the Response
    DescribeGroupResponse (..),
    newDescribeGroupResponse,

    -- * Response Lenses
    describeGroupResponse_description,
    describeGroupResponse_displayName,
    describeGroupResponse_externalIds,
    describeGroupResponse_httpStatus,
    describeGroupResponse_groupId,
    describeGroupResponse_identityStoreId,
  )
where

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

-- | /See:/ 'newDescribeGroup' smart constructor.
data DescribeGroup = DescribeGroup'
  { -- | The globally unique identifier for the identity store, such as
    -- @d-1234567890@. In this example, @d-@ is a fixed prefix, and
    -- @1234567890@ is a randomly generated string that contains numbers and
    -- lower case letters. This value is generated at the time that a new
    -- identity store is created.
    DescribeGroup -> Text
identityStoreId :: Prelude.Text,
    -- | The identifier for a group in the identity store.
    DescribeGroup -> Text
groupId :: Prelude.Text
  }
  deriving (DescribeGroup -> DescribeGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeGroup -> DescribeGroup -> Bool
$c/= :: DescribeGroup -> DescribeGroup -> Bool
== :: DescribeGroup -> DescribeGroup -> Bool
$c== :: DescribeGroup -> DescribeGroup -> Bool
Prelude.Eq, ReadPrec [DescribeGroup]
ReadPrec DescribeGroup
Int -> ReadS DescribeGroup
ReadS [DescribeGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeGroup]
$creadListPrec :: ReadPrec [DescribeGroup]
readPrec :: ReadPrec DescribeGroup
$creadPrec :: ReadPrec DescribeGroup
readList :: ReadS [DescribeGroup]
$creadList :: ReadS [DescribeGroup]
readsPrec :: Int -> ReadS DescribeGroup
$creadsPrec :: Int -> ReadS DescribeGroup
Prelude.Read, Int -> DescribeGroup -> ShowS
[DescribeGroup] -> ShowS
DescribeGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeGroup] -> ShowS
$cshowList :: [DescribeGroup] -> ShowS
show :: DescribeGroup -> String
$cshow :: DescribeGroup -> String
showsPrec :: Int -> DescribeGroup -> ShowS
$cshowsPrec :: Int -> DescribeGroup -> ShowS
Prelude.Show, forall x. Rep DescribeGroup x -> DescribeGroup
forall x. DescribeGroup -> Rep DescribeGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeGroup x -> DescribeGroup
$cfrom :: forall x. DescribeGroup -> Rep DescribeGroup x
Prelude.Generic)

-- |
-- Create a value of 'DescribeGroup' 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:
--
-- 'identityStoreId', 'describeGroup_identityStoreId' - The globally unique identifier for the identity store, such as
-- @d-1234567890@. In this example, @d-@ is a fixed prefix, and
-- @1234567890@ is a randomly generated string that contains numbers and
-- lower case letters. This value is generated at the time that a new
-- identity store is created.
--
-- 'groupId', 'describeGroup_groupId' - The identifier for a group in the identity store.
newDescribeGroup ::
  -- | 'identityStoreId'
  Prelude.Text ->
  -- | 'groupId'
  Prelude.Text ->
  DescribeGroup
newDescribeGroup :: Text -> Text -> DescribeGroup
newDescribeGroup Text
pIdentityStoreId_ Text
pGroupId_ =
  DescribeGroup'
    { $sel:identityStoreId:DescribeGroup' :: Text
identityStoreId = Text
pIdentityStoreId_,
      $sel:groupId:DescribeGroup' :: Text
groupId = Text
pGroupId_
    }

-- | The globally unique identifier for the identity store, such as
-- @d-1234567890@. In this example, @d-@ is a fixed prefix, and
-- @1234567890@ is a randomly generated string that contains numbers and
-- lower case letters. This value is generated at the time that a new
-- identity store is created.
describeGroup_identityStoreId :: Lens.Lens' DescribeGroup Prelude.Text
describeGroup_identityStoreId :: Lens' DescribeGroup Text
describeGroup_identityStoreId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeGroup' {Text
identityStoreId :: Text
$sel:identityStoreId:DescribeGroup' :: DescribeGroup -> Text
identityStoreId} -> Text
identityStoreId) (\s :: DescribeGroup
s@DescribeGroup' {} Text
a -> DescribeGroup
s {$sel:identityStoreId:DescribeGroup' :: Text
identityStoreId = Text
a} :: DescribeGroup)

-- | The identifier for a group in the identity store.
describeGroup_groupId :: Lens.Lens' DescribeGroup Prelude.Text
describeGroup_groupId :: Lens' DescribeGroup Text
describeGroup_groupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeGroup' {Text
groupId :: Text
$sel:groupId:DescribeGroup' :: DescribeGroup -> Text
groupId} -> Text
groupId) (\s :: DescribeGroup
s@DescribeGroup' {} Text
a -> DescribeGroup
s {$sel:groupId:DescribeGroup' :: Text
groupId = Text
a} :: DescribeGroup)

instance Core.AWSRequest DescribeGroup where
  type
    AWSResponse DescribeGroup =
      DescribeGroupResponse
  request :: (Service -> Service) -> DescribeGroup -> Request DescribeGroup
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 DescribeGroup
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeGroup)))
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 (Sensitive Text)
-> Maybe (Sensitive Text)
-> Maybe (NonEmpty ExternalId)
-> Int
-> Text
-> Text
-> DescribeGroupResponse
DescribeGroupResponse'
            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
"Description")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"DisplayName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ExternalIds")
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"GroupId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"IdentityStoreId")
      )

instance Prelude.Hashable DescribeGroup where
  hashWithSalt :: Int -> DescribeGroup -> Int
hashWithSalt Int
_salt DescribeGroup' {Text
groupId :: Text
identityStoreId :: Text
$sel:groupId:DescribeGroup' :: DescribeGroup -> Text
$sel:identityStoreId:DescribeGroup' :: DescribeGroup -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
identityStoreId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
groupId

instance Prelude.NFData DescribeGroup where
  rnf :: DescribeGroup -> ()
rnf DescribeGroup' {Text
groupId :: Text
identityStoreId :: Text
$sel:groupId:DescribeGroup' :: DescribeGroup -> Text
$sel:identityStoreId:DescribeGroup' :: DescribeGroup -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
identityStoreId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
groupId

instance Data.ToHeaders DescribeGroup where
  toHeaders :: DescribeGroup -> 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
"AWSIdentityStore.DescribeGroup" ::
                          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 DescribeGroup where
  toJSON :: DescribeGroup -> Value
toJSON DescribeGroup' {Text
groupId :: Text
identityStoreId :: Text
$sel:groupId:DescribeGroup' :: DescribeGroup -> Text
$sel:identityStoreId:DescribeGroup' :: DescribeGroup -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"IdentityStoreId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
identityStoreId),
            forall a. a -> Maybe a
Prelude.Just (Key
"GroupId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
groupId)
          ]
      )

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

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

-- | /See:/ 'newDescribeGroupResponse' smart constructor.
data DescribeGroupResponse = DescribeGroupResponse'
  { -- | A string containing a description of the group.
    DescribeGroupResponse -> Maybe (Sensitive Text)
description :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The group’s display name value. The length limit is 1,024 characters.
    -- This value can consist of letters, accented characters, symbols,
    -- numbers, punctuation, tab, new line, carriage return, space, and
    -- nonbreaking space in this attribute. This value is specified at the time
    -- that the group is created and stored as an attribute of the group object
    -- in the identity store.
    DescribeGroupResponse -> Maybe (Sensitive Text)
displayName :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | A list of @ExternalId@ objects that contains the identifiers issued to
    -- this resource by an external identity provider.
    DescribeGroupResponse -> Maybe (NonEmpty ExternalId)
externalIds :: Prelude.Maybe (Prelude.NonEmpty ExternalId),
    -- | The response's http status code.
    DescribeGroupResponse -> Int
httpStatus :: Prelude.Int,
    -- | The identifier for a group in the identity store.
    DescribeGroupResponse -> Text
groupId :: Prelude.Text,
    -- | The globally unique identifier for the identity store.
    DescribeGroupResponse -> Text
identityStoreId :: Prelude.Text
  }
  deriving (DescribeGroupResponse -> DescribeGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeGroupResponse -> DescribeGroupResponse -> Bool
$c/= :: DescribeGroupResponse -> DescribeGroupResponse -> Bool
== :: DescribeGroupResponse -> DescribeGroupResponse -> Bool
$c== :: DescribeGroupResponse -> DescribeGroupResponse -> Bool
Prelude.Eq, Int -> DescribeGroupResponse -> ShowS
[DescribeGroupResponse] -> ShowS
DescribeGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeGroupResponse] -> ShowS
$cshowList :: [DescribeGroupResponse] -> ShowS
show :: DescribeGroupResponse -> String
$cshow :: DescribeGroupResponse -> String
showsPrec :: Int -> DescribeGroupResponse -> ShowS
$cshowsPrec :: Int -> DescribeGroupResponse -> ShowS
Prelude.Show, forall x. Rep DescribeGroupResponse x -> DescribeGroupResponse
forall x. DescribeGroupResponse -> Rep DescribeGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeGroupResponse x -> DescribeGroupResponse
$cfrom :: forall x. DescribeGroupResponse -> Rep DescribeGroupResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeGroupResponse' 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:
--
-- 'description', 'describeGroupResponse_description' - A string containing a description of the group.
--
-- 'displayName', 'describeGroupResponse_displayName' - The group’s display name value. The length limit is 1,024 characters.
-- This value can consist of letters, accented characters, symbols,
-- numbers, punctuation, tab, new line, carriage return, space, and
-- nonbreaking space in this attribute. This value is specified at the time
-- that the group is created and stored as an attribute of the group object
-- in the identity store.
--
-- 'externalIds', 'describeGroupResponse_externalIds' - A list of @ExternalId@ objects that contains the identifiers issued to
-- this resource by an external identity provider.
--
-- 'httpStatus', 'describeGroupResponse_httpStatus' - The response's http status code.
--
-- 'groupId', 'describeGroupResponse_groupId' - The identifier for a group in the identity store.
--
-- 'identityStoreId', 'describeGroupResponse_identityStoreId' - The globally unique identifier for the identity store.
newDescribeGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'groupId'
  Prelude.Text ->
  -- | 'identityStoreId'
  Prelude.Text ->
  DescribeGroupResponse
newDescribeGroupResponse :: Int -> Text -> Text -> DescribeGroupResponse
newDescribeGroupResponse
  Int
pHttpStatus_
  Text
pGroupId_
  Text
pIdentityStoreId_ =
    DescribeGroupResponse'
      { $sel:description:DescribeGroupResponse' :: Maybe (Sensitive Text)
description =
          forall a. Maybe a
Prelude.Nothing,
        $sel:displayName:DescribeGroupResponse' :: Maybe (Sensitive Text)
displayName = forall a. Maybe a
Prelude.Nothing,
        $sel:externalIds:DescribeGroupResponse' :: Maybe (NonEmpty ExternalId)
externalIds = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeGroupResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:groupId:DescribeGroupResponse' :: Text
groupId = Text
pGroupId_,
        $sel:identityStoreId:DescribeGroupResponse' :: Text
identityStoreId = Text
pIdentityStoreId_
      }

-- | A string containing a description of the group.
describeGroupResponse_description :: Lens.Lens' DescribeGroupResponse (Prelude.Maybe Prelude.Text)
describeGroupResponse_description :: Lens' DescribeGroupResponse (Maybe Text)
describeGroupResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeGroupResponse' {Maybe (Sensitive Text)
description :: Maybe (Sensitive Text)
$sel:description:DescribeGroupResponse' :: DescribeGroupResponse -> Maybe (Sensitive Text)
description} -> Maybe (Sensitive Text)
description) (\s :: DescribeGroupResponse
s@DescribeGroupResponse' {} Maybe (Sensitive Text)
a -> DescribeGroupResponse
s {$sel:description:DescribeGroupResponse' :: Maybe (Sensitive Text)
description = Maybe (Sensitive Text)
a} :: DescribeGroupResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | The group’s display name value. The length limit is 1,024 characters.
-- This value can consist of letters, accented characters, symbols,
-- numbers, punctuation, tab, new line, carriage return, space, and
-- nonbreaking space in this attribute. This value is specified at the time
-- that the group is created and stored as an attribute of the group object
-- in the identity store.
describeGroupResponse_displayName :: Lens.Lens' DescribeGroupResponse (Prelude.Maybe Prelude.Text)
describeGroupResponse_displayName :: Lens' DescribeGroupResponse (Maybe Text)
describeGroupResponse_displayName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeGroupResponse' {Maybe (Sensitive Text)
displayName :: Maybe (Sensitive Text)
$sel:displayName:DescribeGroupResponse' :: DescribeGroupResponse -> Maybe (Sensitive Text)
displayName} -> Maybe (Sensitive Text)
displayName) (\s :: DescribeGroupResponse
s@DescribeGroupResponse' {} Maybe (Sensitive Text)
a -> DescribeGroupResponse
s {$sel:displayName:DescribeGroupResponse' :: Maybe (Sensitive Text)
displayName = Maybe (Sensitive Text)
a} :: DescribeGroupResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | A list of @ExternalId@ objects that contains the identifiers issued to
-- this resource by an external identity provider.
describeGroupResponse_externalIds :: Lens.Lens' DescribeGroupResponse (Prelude.Maybe (Prelude.NonEmpty ExternalId))
describeGroupResponse_externalIds :: Lens' DescribeGroupResponse (Maybe (NonEmpty ExternalId))
describeGroupResponse_externalIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeGroupResponse' {Maybe (NonEmpty ExternalId)
externalIds :: Maybe (NonEmpty ExternalId)
$sel:externalIds:DescribeGroupResponse' :: DescribeGroupResponse -> Maybe (NonEmpty ExternalId)
externalIds} -> Maybe (NonEmpty ExternalId)
externalIds) (\s :: DescribeGroupResponse
s@DescribeGroupResponse' {} Maybe (NonEmpty ExternalId)
a -> DescribeGroupResponse
s {$sel:externalIds:DescribeGroupResponse' :: Maybe (NonEmpty ExternalId)
externalIds = Maybe (NonEmpty ExternalId)
a} :: DescribeGroupResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

-- | The identifier for a group in the identity store.
describeGroupResponse_groupId :: Lens.Lens' DescribeGroupResponse Prelude.Text
describeGroupResponse_groupId :: Lens' DescribeGroupResponse Text
describeGroupResponse_groupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeGroupResponse' {Text
groupId :: Text
$sel:groupId:DescribeGroupResponse' :: DescribeGroupResponse -> Text
groupId} -> Text
groupId) (\s :: DescribeGroupResponse
s@DescribeGroupResponse' {} Text
a -> DescribeGroupResponse
s {$sel:groupId:DescribeGroupResponse' :: Text
groupId = Text
a} :: DescribeGroupResponse)

-- | The globally unique identifier for the identity store.
describeGroupResponse_identityStoreId :: Lens.Lens' DescribeGroupResponse Prelude.Text
describeGroupResponse_identityStoreId :: Lens' DescribeGroupResponse Text
describeGroupResponse_identityStoreId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeGroupResponse' {Text
identityStoreId :: Text
$sel:identityStoreId:DescribeGroupResponse' :: DescribeGroupResponse -> Text
identityStoreId} -> Text
identityStoreId) (\s :: DescribeGroupResponse
s@DescribeGroupResponse' {} Text
a -> DescribeGroupResponse
s {$sel:identityStoreId:DescribeGroupResponse' :: Text
identityStoreId = Text
a} :: DescribeGroupResponse)

instance Prelude.NFData DescribeGroupResponse where
  rnf :: DescribeGroupResponse -> ()
rnf DescribeGroupResponse' {Int
Maybe (NonEmpty ExternalId)
Maybe (Sensitive Text)
Text
identityStoreId :: Text
groupId :: Text
httpStatus :: Int
externalIds :: Maybe (NonEmpty ExternalId)
displayName :: Maybe (Sensitive Text)
description :: Maybe (Sensitive Text)
$sel:identityStoreId:DescribeGroupResponse' :: DescribeGroupResponse -> Text
$sel:groupId:DescribeGroupResponse' :: DescribeGroupResponse -> Text
$sel:httpStatus:DescribeGroupResponse' :: DescribeGroupResponse -> Int
$sel:externalIds:DescribeGroupResponse' :: DescribeGroupResponse -> Maybe (NonEmpty ExternalId)
$sel:displayName:DescribeGroupResponse' :: DescribeGroupResponse -> Maybe (Sensitive Text)
$sel:description:DescribeGroupResponse' :: DescribeGroupResponse -> Maybe (Sensitive Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
displayName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty ExternalId)
externalIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
groupId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
identityStoreId