{-# 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.GetGroupMembershipId
-- 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 @MembershipId@ in an identity store.
module Amazonka.IdentityStore.GetGroupMembershipId
  ( -- * Creating a Request
    GetGroupMembershipId (..),
    newGetGroupMembershipId,

    -- * Request Lenses
    getGroupMembershipId_identityStoreId,
    getGroupMembershipId_groupId,
    getGroupMembershipId_memberId,

    -- * Destructuring the Response
    GetGroupMembershipIdResponse (..),
    newGetGroupMembershipIdResponse,

    -- * Response Lenses
    getGroupMembershipIdResponse_httpStatus,
    getGroupMembershipIdResponse_membershipId,
    getGroupMembershipIdResponse_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:/ 'newGetGroupMembershipId' smart constructor.
data GetGroupMembershipId = GetGroupMembershipId'
  { -- | The globally unique identifier for the identity store.
    GetGroupMembershipId -> Text
identityStoreId :: Prelude.Text,
    -- | The identifier for a group in the identity store.
    GetGroupMembershipId -> Text
groupId :: Prelude.Text,
    -- | An object that contains the identifier of a group member. Setting the
    -- @UserID@ field to the specific identifier for a user indicates that the
    -- user is a member of the group.
    GetGroupMembershipId -> MemberId
memberId :: MemberId
  }
  deriving (GetGroupMembershipId -> GetGroupMembershipId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetGroupMembershipId -> GetGroupMembershipId -> Bool
$c/= :: GetGroupMembershipId -> GetGroupMembershipId -> Bool
== :: GetGroupMembershipId -> GetGroupMembershipId -> Bool
$c== :: GetGroupMembershipId -> GetGroupMembershipId -> Bool
Prelude.Eq, ReadPrec [GetGroupMembershipId]
ReadPrec GetGroupMembershipId
Int -> ReadS GetGroupMembershipId
ReadS [GetGroupMembershipId]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetGroupMembershipId]
$creadListPrec :: ReadPrec [GetGroupMembershipId]
readPrec :: ReadPrec GetGroupMembershipId
$creadPrec :: ReadPrec GetGroupMembershipId
readList :: ReadS [GetGroupMembershipId]
$creadList :: ReadS [GetGroupMembershipId]
readsPrec :: Int -> ReadS GetGroupMembershipId
$creadsPrec :: Int -> ReadS GetGroupMembershipId
Prelude.Read, Int -> GetGroupMembershipId -> ShowS
[GetGroupMembershipId] -> ShowS
GetGroupMembershipId -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetGroupMembershipId] -> ShowS
$cshowList :: [GetGroupMembershipId] -> ShowS
show :: GetGroupMembershipId -> String
$cshow :: GetGroupMembershipId -> String
showsPrec :: Int -> GetGroupMembershipId -> ShowS
$cshowsPrec :: Int -> GetGroupMembershipId -> ShowS
Prelude.Show, forall x. Rep GetGroupMembershipId x -> GetGroupMembershipId
forall x. GetGroupMembershipId -> Rep GetGroupMembershipId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetGroupMembershipId x -> GetGroupMembershipId
$cfrom :: forall x. GetGroupMembershipId -> Rep GetGroupMembershipId x
Prelude.Generic)

-- |
-- Create a value of 'GetGroupMembershipId' 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', 'getGroupMembershipId_identityStoreId' - The globally unique identifier for the identity store.
--
-- 'groupId', 'getGroupMembershipId_groupId' - The identifier for a group in the identity store.
--
-- 'memberId', 'getGroupMembershipId_memberId' - An object that contains the identifier of a group member. Setting the
-- @UserID@ field to the specific identifier for a user indicates that the
-- user is a member of the group.
newGetGroupMembershipId ::
  -- | 'identityStoreId'
  Prelude.Text ->
  -- | 'groupId'
  Prelude.Text ->
  -- | 'memberId'
  MemberId ->
  GetGroupMembershipId
newGetGroupMembershipId :: Text -> Text -> MemberId -> GetGroupMembershipId
newGetGroupMembershipId
  Text
pIdentityStoreId_
  Text
pGroupId_
  MemberId
pMemberId_ =
    GetGroupMembershipId'
      { $sel:identityStoreId:GetGroupMembershipId' :: Text
identityStoreId =
          Text
pIdentityStoreId_,
        $sel:groupId:GetGroupMembershipId' :: Text
groupId = Text
pGroupId_,
        $sel:memberId:GetGroupMembershipId' :: MemberId
memberId = MemberId
pMemberId_
      }

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

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

-- | An object that contains the identifier of a group member. Setting the
-- @UserID@ field to the specific identifier for a user indicates that the
-- user is a member of the group.
getGroupMembershipId_memberId :: Lens.Lens' GetGroupMembershipId MemberId
getGroupMembershipId_memberId :: Lens' GetGroupMembershipId MemberId
getGroupMembershipId_memberId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGroupMembershipId' {MemberId
memberId :: MemberId
$sel:memberId:GetGroupMembershipId' :: GetGroupMembershipId -> MemberId
memberId} -> MemberId
memberId) (\s :: GetGroupMembershipId
s@GetGroupMembershipId' {} MemberId
a -> GetGroupMembershipId
s {$sel:memberId:GetGroupMembershipId' :: MemberId
memberId = MemberId
a} :: GetGroupMembershipId)

instance Core.AWSRequest GetGroupMembershipId where
  type
    AWSResponse GetGroupMembershipId =
      GetGroupMembershipIdResponse
  request :: (Service -> Service)
-> GetGroupMembershipId -> Request GetGroupMembershipId
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 GetGroupMembershipId
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetGroupMembershipId)))
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 ->
          Int -> Text -> Text -> GetGroupMembershipIdResponse
GetGroupMembershipIdResponse'
            forall (f :: * -> *) a b. Functor 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
"MembershipId")
            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 GetGroupMembershipId where
  hashWithSalt :: Int -> GetGroupMembershipId -> Int
hashWithSalt Int
_salt GetGroupMembershipId' {Text
MemberId
memberId :: MemberId
groupId :: Text
identityStoreId :: Text
$sel:memberId:GetGroupMembershipId' :: GetGroupMembershipId -> MemberId
$sel:groupId:GetGroupMembershipId' :: GetGroupMembershipId -> Text
$sel:identityStoreId:GetGroupMembershipId' :: GetGroupMembershipId -> 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
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` MemberId
memberId

instance Prelude.NFData GetGroupMembershipId where
  rnf :: GetGroupMembershipId -> ()
rnf GetGroupMembershipId' {Text
MemberId
memberId :: MemberId
groupId :: Text
identityStoreId :: Text
$sel:memberId:GetGroupMembershipId' :: GetGroupMembershipId -> MemberId
$sel:groupId:GetGroupMembershipId' :: GetGroupMembershipId -> Text
$sel:identityStoreId:GetGroupMembershipId' :: GetGroupMembershipId -> 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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf MemberId
memberId

instance Data.ToHeaders GetGroupMembershipId where
  toHeaders :: GetGroupMembershipId -> 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.GetGroupMembershipId" ::
                          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 GetGroupMembershipId where
  toJSON :: GetGroupMembershipId -> Value
toJSON GetGroupMembershipId' {Text
MemberId
memberId :: MemberId
groupId :: Text
identityStoreId :: Text
$sel:memberId:GetGroupMembershipId' :: GetGroupMembershipId -> MemberId
$sel:groupId:GetGroupMembershipId' :: GetGroupMembershipId -> Text
$sel:identityStoreId:GetGroupMembershipId' :: GetGroupMembershipId -> 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),
            forall a. a -> Maybe a
Prelude.Just (Key
"MemberId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= MemberId
memberId)
          ]
      )

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

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

-- | /See:/ 'newGetGroupMembershipIdResponse' smart constructor.
data GetGroupMembershipIdResponse = GetGroupMembershipIdResponse'
  { -- | The response's http status code.
    GetGroupMembershipIdResponse -> Int
httpStatus :: Prelude.Int,
    -- | The identifier for a @GroupMembership@ in an identity store.
    GetGroupMembershipIdResponse -> Text
membershipId :: Prelude.Text,
    -- | The globally unique identifier for the identity store.
    GetGroupMembershipIdResponse -> Text
identityStoreId :: Prelude.Text
  }
  deriving (GetGroupMembershipIdResponse
-> GetGroupMembershipIdResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetGroupMembershipIdResponse
-> GetGroupMembershipIdResponse -> Bool
$c/= :: GetGroupMembershipIdResponse
-> GetGroupMembershipIdResponse -> Bool
== :: GetGroupMembershipIdResponse
-> GetGroupMembershipIdResponse -> Bool
$c== :: GetGroupMembershipIdResponse
-> GetGroupMembershipIdResponse -> Bool
Prelude.Eq, ReadPrec [GetGroupMembershipIdResponse]
ReadPrec GetGroupMembershipIdResponse
Int -> ReadS GetGroupMembershipIdResponse
ReadS [GetGroupMembershipIdResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetGroupMembershipIdResponse]
$creadListPrec :: ReadPrec [GetGroupMembershipIdResponse]
readPrec :: ReadPrec GetGroupMembershipIdResponse
$creadPrec :: ReadPrec GetGroupMembershipIdResponse
readList :: ReadS [GetGroupMembershipIdResponse]
$creadList :: ReadS [GetGroupMembershipIdResponse]
readsPrec :: Int -> ReadS GetGroupMembershipIdResponse
$creadsPrec :: Int -> ReadS GetGroupMembershipIdResponse
Prelude.Read, Int -> GetGroupMembershipIdResponse -> ShowS
[GetGroupMembershipIdResponse] -> ShowS
GetGroupMembershipIdResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetGroupMembershipIdResponse] -> ShowS
$cshowList :: [GetGroupMembershipIdResponse] -> ShowS
show :: GetGroupMembershipIdResponse -> String
$cshow :: GetGroupMembershipIdResponse -> String
showsPrec :: Int -> GetGroupMembershipIdResponse -> ShowS
$cshowsPrec :: Int -> GetGroupMembershipIdResponse -> ShowS
Prelude.Show, forall x.
Rep GetGroupMembershipIdResponse x -> GetGroupMembershipIdResponse
forall x.
GetGroupMembershipIdResponse -> Rep GetGroupMembershipIdResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetGroupMembershipIdResponse x -> GetGroupMembershipIdResponse
$cfrom :: forall x.
GetGroupMembershipIdResponse -> Rep GetGroupMembershipIdResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetGroupMembershipIdResponse' 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:
--
-- 'httpStatus', 'getGroupMembershipIdResponse_httpStatus' - The response's http status code.
--
-- 'membershipId', 'getGroupMembershipIdResponse_membershipId' - The identifier for a @GroupMembership@ in an identity store.
--
-- 'identityStoreId', 'getGroupMembershipIdResponse_identityStoreId' - The globally unique identifier for the identity store.
newGetGroupMembershipIdResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'membershipId'
  Prelude.Text ->
  -- | 'identityStoreId'
  Prelude.Text ->
  GetGroupMembershipIdResponse
newGetGroupMembershipIdResponse :: Int -> Text -> Text -> GetGroupMembershipIdResponse
newGetGroupMembershipIdResponse
  Int
pHttpStatus_
  Text
pMembershipId_
  Text
pIdentityStoreId_ =
    GetGroupMembershipIdResponse'
      { $sel:httpStatus:GetGroupMembershipIdResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:membershipId:GetGroupMembershipIdResponse' :: Text
membershipId = Text
pMembershipId_,
        $sel:identityStoreId:GetGroupMembershipIdResponse' :: Text
identityStoreId = Text
pIdentityStoreId_
      }

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

-- | The identifier for a @GroupMembership@ in an identity store.
getGroupMembershipIdResponse_membershipId :: Lens.Lens' GetGroupMembershipIdResponse Prelude.Text
getGroupMembershipIdResponse_membershipId :: Lens' GetGroupMembershipIdResponse Text
getGroupMembershipIdResponse_membershipId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGroupMembershipIdResponse' {Text
membershipId :: Text
$sel:membershipId:GetGroupMembershipIdResponse' :: GetGroupMembershipIdResponse -> Text
membershipId} -> Text
membershipId) (\s :: GetGroupMembershipIdResponse
s@GetGroupMembershipIdResponse' {} Text
a -> GetGroupMembershipIdResponse
s {$sel:membershipId:GetGroupMembershipIdResponse' :: Text
membershipId = Text
a} :: GetGroupMembershipIdResponse)

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

instance Prelude.NFData GetGroupMembershipIdResponse where
  rnf :: GetGroupMembershipIdResponse -> ()
rnf GetGroupMembershipIdResponse' {Int
Text
identityStoreId :: Text
membershipId :: Text
httpStatus :: Int
$sel:identityStoreId:GetGroupMembershipIdResponse' :: GetGroupMembershipIdResponse -> Text
$sel:membershipId:GetGroupMembershipIdResponse' :: GetGroupMembershipIdResponse -> Text
$sel:httpStatus:GetGroupMembershipIdResponse' :: GetGroupMembershipIdResponse -> Int
..} =
    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
membershipId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
identityStoreId