{-# 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.ListGroups -- Copyright : (c) 2013-2023 Brendan Hay -- License : Mozilla Public License, v. 2.0. -- Maintainer : Brendan Hay -- Stability : auto-generated -- Portability : non-portable (GHC extensions) -- -- Lists the groups associated with a user pool. -- -- Calling this action requires developer credentials. -- -- This operation returns paginated results. module Amazonka.CognitoIdentityProvider.ListGroups ( -- * Creating a Request ListGroups (..), newListGroups, -- * Request Lenses listGroups_limit, listGroups_nextToken, listGroups_userPoolId, -- * Destructuring the Response ListGroupsResponse (..), newListGroupsResponse, -- * Response Lenses listGroupsResponse_groups, listGroupsResponse_nextToken, listGroupsResponse_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:/ 'newListGroups' smart constructor. data ListGroups = ListGroups' { -- | The limit of the request to list groups. limit :: Prelude.Maybe Prelude.Natural, -- | An identifier that was returned from the previous call to this -- operation, which can be used to return the next set of items in the -- list. nextToken :: Prelude.Maybe Prelude.Text, -- | The user pool ID for the user pool. userPoolId :: Prelude.Text } deriving (Prelude.Eq, Prelude.Read, Prelude.Show, Prelude.Generic) -- | -- Create a value of 'ListGroups' with all optional fields omitted. -- -- Use or to modify other optional fields. -- -- The following record fields are available, with the corresponding lenses provided -- for backwards compatibility: -- -- 'limit', 'listGroups_limit' - The limit of the request to list groups. -- -- 'nextToken', 'listGroups_nextToken' - An identifier that was returned from the previous call to this -- operation, which can be used to return the next set of items in the -- list. -- -- 'userPoolId', 'listGroups_userPoolId' - The user pool ID for the user pool. newListGroups :: -- | 'userPoolId' Prelude.Text -> ListGroups newListGroups pUserPoolId_ = ListGroups' { limit = Prelude.Nothing, nextToken = Prelude.Nothing, userPoolId = pUserPoolId_ } -- | The limit of the request to list groups. listGroups_limit :: Lens.Lens' ListGroups (Prelude.Maybe Prelude.Natural) listGroups_limit = Lens.lens (\ListGroups' {limit} -> limit) (\s@ListGroups' {} a -> s {limit = a} :: ListGroups) -- | An identifier that was returned from the previous call to this -- operation, which can be used to return the next set of items in the -- list. listGroups_nextToken :: Lens.Lens' ListGroups (Prelude.Maybe Prelude.Text) listGroups_nextToken = Lens.lens (\ListGroups' {nextToken} -> nextToken) (\s@ListGroups' {} a -> s {nextToken = a} :: ListGroups) -- | The user pool ID for the user pool. listGroups_userPoolId :: Lens.Lens' ListGroups Prelude.Text listGroups_userPoolId = Lens.lens (\ListGroups' {userPoolId} -> userPoolId) (\s@ListGroups' {} a -> s {userPoolId = a} :: ListGroups) instance Core.AWSPager ListGroups where page rq rs | Core.stop ( rs Lens.^? listGroupsResponse_nextToken Prelude.. Lens._Just ) = Prelude.Nothing | Core.stop ( rs Lens.^? listGroupsResponse_groups Prelude.. Lens._Just ) = Prelude.Nothing | Prelude.otherwise = Prelude.Just Prelude.$ rq Prelude.& listGroups_nextToken Lens..~ rs Lens.^? listGroupsResponse_nextToken Prelude.. Lens._Just instance Core.AWSRequest ListGroups where type AWSResponse ListGroups = ListGroupsResponse request overrides = Request.postJSON (overrides defaultService) response = Response.receiveJSON ( \s h x -> ListGroupsResponse' Prelude.<$> (x Data..?> "Groups" Core..!@ Prelude.mempty) Prelude.<*> (x Data..?> "NextToken") Prelude.<*> (Prelude.pure (Prelude.fromEnum s)) ) instance Prelude.Hashable ListGroups where hashWithSalt _salt ListGroups' {..} = _salt `Prelude.hashWithSalt` limit `Prelude.hashWithSalt` nextToken `Prelude.hashWithSalt` userPoolId instance Prelude.NFData ListGroups where rnf ListGroups' {..} = Prelude.rnf limit `Prelude.seq` Prelude.rnf nextToken `Prelude.seq` Prelude.rnf userPoolId instance Data.ToHeaders ListGroups where toHeaders = Prelude.const ( Prelude.mconcat [ "X-Amz-Target" Data.=# ( "AWSCognitoIdentityProviderService.ListGroups" :: Prelude.ByteString ), "Content-Type" Data.=# ( "application/x-amz-json-1.1" :: Prelude.ByteString ) ] ) instance Data.ToJSON ListGroups where toJSON ListGroups' {..} = Data.object ( Prelude.catMaybes [ ("Limit" Data..=) Prelude.<$> limit, ("NextToken" Data..=) Prelude.<$> nextToken, Prelude.Just ("UserPoolId" Data..= userPoolId) ] ) instance Data.ToPath ListGroups where toPath = Prelude.const "/" instance Data.ToQuery ListGroups where toQuery = Prelude.const Prelude.mempty -- | /See:/ 'newListGroupsResponse' smart constructor. data ListGroupsResponse = ListGroupsResponse' { -- | The group objects for the groups. groups :: Prelude.Maybe [GroupType], -- | An identifier that was returned from the previous call to this -- operation, which can be used to return the next set of items in the -- list. nextToken :: Prelude.Maybe Prelude.Text, -- | The response's http status code. httpStatus :: Prelude.Int } deriving (Prelude.Eq, Prelude.Read, Prelude.Show, Prelude.Generic) -- | -- Create a value of 'ListGroupsResponse' with all optional fields omitted. -- -- Use or to modify other optional fields. -- -- The following record fields are available, with the corresponding lenses provided -- for backwards compatibility: -- -- 'groups', 'listGroupsResponse_groups' - The group objects for the groups. -- -- 'nextToken', 'listGroupsResponse_nextToken' - An identifier that was returned from the previous call to this -- operation, which can be used to return the next set of items in the -- list. -- -- 'httpStatus', 'listGroupsResponse_httpStatus' - The response's http status code. newListGroupsResponse :: -- | 'httpStatus' Prelude.Int -> ListGroupsResponse newListGroupsResponse pHttpStatus_ = ListGroupsResponse' { groups = Prelude.Nothing, nextToken = Prelude.Nothing, httpStatus = pHttpStatus_ } -- | The group objects for the groups. listGroupsResponse_groups :: Lens.Lens' ListGroupsResponse (Prelude.Maybe [GroupType]) listGroupsResponse_groups = Lens.lens (\ListGroupsResponse' {groups} -> groups) (\s@ListGroupsResponse' {} a -> s {groups = a} :: ListGroupsResponse) Prelude.. Lens.mapping Lens.coerced -- | An identifier that was returned from the previous call to this -- operation, which can be used to return the next set of items in the -- list. listGroupsResponse_nextToken :: Lens.Lens' ListGroupsResponse (Prelude.Maybe Prelude.Text) listGroupsResponse_nextToken = Lens.lens (\ListGroupsResponse' {nextToken} -> nextToken) (\s@ListGroupsResponse' {} a -> s {nextToken = a} :: ListGroupsResponse) -- | The response's http status code. listGroupsResponse_httpStatus :: Lens.Lens' ListGroupsResponse Prelude.Int listGroupsResponse_httpStatus = Lens.lens (\ListGroupsResponse' {httpStatus} -> httpStatus) (\s@ListGroupsResponse' {} a -> s {httpStatus = a} :: ListGroupsResponse) instance Prelude.NFData ListGroupsResponse where rnf ListGroupsResponse' {..} = Prelude.rnf groups `Prelude.seq` Prelude.rnf nextToken `Prelude.seq` Prelude.rnf httpStatus