{-# 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.RAM.ListPrincipals
-- 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 principals that you are sharing resources with or that are
-- sharing resources with you.
--
-- This operation returns paginated results.
module Amazonka.RAM.ListPrincipals
  ( -- * Creating a Request
    ListPrincipals (..),
    newListPrincipals,

    -- * Request Lenses
    listPrincipals_maxResults,
    listPrincipals_nextToken,
    listPrincipals_principals,
    listPrincipals_resourceArn,
    listPrincipals_resourceShareArns,
    listPrincipals_resourceType,
    listPrincipals_resourceOwner,

    -- * Destructuring the Response
    ListPrincipalsResponse (..),
    newListPrincipalsResponse,

    -- * Response Lenses
    listPrincipalsResponse_nextToken,
    listPrincipalsResponse_principals,
    listPrincipalsResponse_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 Amazonka.RAM.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newListPrincipals' smart constructor.
data ListPrincipals = ListPrincipals'
  { -- | Specifies the total number of results that you want included on each
    -- page of the response. If you do not include this parameter, it defaults
    -- to a value that is specific to the operation. If additional items exist
    -- beyond the number you specify, the @NextToken@ response element is
    -- returned with a value (not null). Include the specified value as the
    -- @NextToken@ request parameter in the next call to the operation to get
    -- the next part of the results. Note that the service might return fewer
    -- results than the maximum even when there are more results available. You
    -- should check @NextToken@ after every operation to ensure that you
    -- receive all of the results.
    ListPrincipals -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | Specifies that you want to receive the next page of results. Valid only
    -- if you received a @NextToken@ response in the previous request. If you
    -- did, it indicates that more output is available. Set this parameter to
    -- the value provided by the previous call\'s @NextToken@ response to
    -- request the next page of results.
    ListPrincipals -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Specifies that you want to list information for only the listed
    -- principals.
    --
    -- You can include the following values:
    --
    -- -   An Amazon Web Services account ID, for example: @123456789012@
    --
    -- -   An
    --     <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
    --     of an organization in Organizations, for example:
    --     @organizations::123456789012:organization\/o-exampleorgid@
    --
    -- -   An ARN of an organizational unit (OU) in Organizations, for example:
    --     @organizations::123456789012:ou\/o-exampleorgid\/ou-examplerootid-exampleouid123@
    --
    -- -   An ARN of an IAM role, for example:
    --     @iam::123456789012:role\/rolename@
    --
    -- -   An ARN of an IAM user, for example:
    --     @iam::123456789012user\/username@
    --
    -- Not all resource types can be shared with IAM roles and users. For more
    -- information, see
    -- <https://docs.aws.amazon.com/ram/latest/userguide/permissions.html#permissions-rbp-supported-resource-types Sharing with IAM roles and users>
    -- in the /Resource Access Manager User Guide/.
    ListPrincipals -> Maybe [Text]
principals :: Prelude.Maybe [Prelude.Text],
    -- | Specifies that you want to list principal information for the resource
    -- share with the specified
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>.
    ListPrincipals -> Maybe Text
resourceArn :: Prelude.Maybe Prelude.Text,
    -- | Specifies that you want to list information for only principals
    -- associated with the resource shares specified by a list the
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>.
    ListPrincipals -> Maybe [Text]
resourceShareArns :: Prelude.Maybe [Prelude.Text],
    -- | Specifies that you want to list information for only principals
    -- associated with resource shares that include the specified resource
    -- type.
    --
    -- For a list of valid values, query the ListResourceTypes operation.
    ListPrincipals -> Maybe Text
resourceType :: Prelude.Maybe Prelude.Text,
    -- | Specifies that you want to list information for only resource shares
    -- that match the following:
    --
    -- -   __@SELF@__ – principals that your account is sharing resources with
    --
    -- -   __@OTHER-ACCOUNTS@__ – principals that are sharing resources with
    --     your account
    ListPrincipals -> ResourceOwner
resourceOwner :: ResourceOwner
  }
  deriving (ListPrincipals -> ListPrincipals -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPrincipals -> ListPrincipals -> Bool
$c/= :: ListPrincipals -> ListPrincipals -> Bool
== :: ListPrincipals -> ListPrincipals -> Bool
$c== :: ListPrincipals -> ListPrincipals -> Bool
Prelude.Eq, ReadPrec [ListPrincipals]
ReadPrec ListPrincipals
Int -> ReadS ListPrincipals
ReadS [ListPrincipals]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPrincipals]
$creadListPrec :: ReadPrec [ListPrincipals]
readPrec :: ReadPrec ListPrincipals
$creadPrec :: ReadPrec ListPrincipals
readList :: ReadS [ListPrincipals]
$creadList :: ReadS [ListPrincipals]
readsPrec :: Int -> ReadS ListPrincipals
$creadsPrec :: Int -> ReadS ListPrincipals
Prelude.Read, Int -> ListPrincipals -> ShowS
[ListPrincipals] -> ShowS
ListPrincipals -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPrincipals] -> ShowS
$cshowList :: [ListPrincipals] -> ShowS
show :: ListPrincipals -> String
$cshow :: ListPrincipals -> String
showsPrec :: Int -> ListPrincipals -> ShowS
$cshowsPrec :: Int -> ListPrincipals -> ShowS
Prelude.Show, forall x. Rep ListPrincipals x -> ListPrincipals
forall x. ListPrincipals -> Rep ListPrincipals x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListPrincipals x -> ListPrincipals
$cfrom :: forall x. ListPrincipals -> Rep ListPrincipals x
Prelude.Generic)

-- |
-- Create a value of 'ListPrincipals' 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:
--
-- 'maxResults', 'listPrincipals_maxResults' - Specifies the total number of results that you want included on each
-- page of the response. If you do not include this parameter, it defaults
-- to a value that is specific to the operation. If additional items exist
-- beyond the number you specify, the @NextToken@ response element is
-- returned with a value (not null). Include the specified value as the
-- @NextToken@ request parameter in the next call to the operation to get
-- the next part of the results. Note that the service might return fewer
-- results than the maximum even when there are more results available. You
-- should check @NextToken@ after every operation to ensure that you
-- receive all of the results.
--
-- 'nextToken', 'listPrincipals_nextToken' - Specifies that you want to receive the next page of results. Valid only
-- if you received a @NextToken@ response in the previous request. If you
-- did, it indicates that more output is available. Set this parameter to
-- the value provided by the previous call\'s @NextToken@ response to
-- request the next page of results.
--
-- 'principals', 'listPrincipals_principals' - Specifies that you want to list information for only the listed
-- principals.
--
-- You can include the following values:
--
-- -   An Amazon Web Services account ID, for example: @123456789012@
--
-- -   An
--     <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
--     of an organization in Organizations, for example:
--     @organizations::123456789012:organization\/o-exampleorgid@
--
-- -   An ARN of an organizational unit (OU) in Organizations, for example:
--     @organizations::123456789012:ou\/o-exampleorgid\/ou-examplerootid-exampleouid123@
--
-- -   An ARN of an IAM role, for example:
--     @iam::123456789012:role\/rolename@
--
-- -   An ARN of an IAM user, for example:
--     @iam::123456789012user\/username@
--
-- Not all resource types can be shared with IAM roles and users. For more
-- information, see
-- <https://docs.aws.amazon.com/ram/latest/userguide/permissions.html#permissions-rbp-supported-resource-types Sharing with IAM roles and users>
-- in the /Resource Access Manager User Guide/.
--
-- 'resourceArn', 'listPrincipals_resourceArn' - Specifies that you want to list principal information for the resource
-- share with the specified
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>.
--
-- 'resourceShareArns', 'listPrincipals_resourceShareArns' - Specifies that you want to list information for only principals
-- associated with the resource shares specified by a list the
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>.
--
-- 'resourceType', 'listPrincipals_resourceType' - Specifies that you want to list information for only principals
-- associated with resource shares that include the specified resource
-- type.
--
-- For a list of valid values, query the ListResourceTypes operation.
--
-- 'resourceOwner', 'listPrincipals_resourceOwner' - Specifies that you want to list information for only resource shares
-- that match the following:
--
-- -   __@SELF@__ – principals that your account is sharing resources with
--
-- -   __@OTHER-ACCOUNTS@__ – principals that are sharing resources with
--     your account
newListPrincipals ::
  -- | 'resourceOwner'
  ResourceOwner ->
  ListPrincipals
newListPrincipals :: ResourceOwner -> ListPrincipals
newListPrincipals ResourceOwner
pResourceOwner_ =
  ListPrincipals'
    { $sel:maxResults:ListPrincipals' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListPrincipals' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:principals:ListPrincipals' :: Maybe [Text]
principals = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceArn:ListPrincipals' :: Maybe Text
resourceArn = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceShareArns:ListPrincipals' :: Maybe [Text]
resourceShareArns = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceType:ListPrincipals' :: Maybe Text
resourceType = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceOwner:ListPrincipals' :: ResourceOwner
resourceOwner = ResourceOwner
pResourceOwner_
    }

-- | Specifies the total number of results that you want included on each
-- page of the response. If you do not include this parameter, it defaults
-- to a value that is specific to the operation. If additional items exist
-- beyond the number you specify, the @NextToken@ response element is
-- returned with a value (not null). Include the specified value as the
-- @NextToken@ request parameter in the next call to the operation to get
-- the next part of the results. Note that the service might return fewer
-- results than the maximum even when there are more results available. You
-- should check @NextToken@ after every operation to ensure that you
-- receive all of the results.
listPrincipals_maxResults :: Lens.Lens' ListPrincipals (Prelude.Maybe Prelude.Natural)
listPrincipals_maxResults :: Lens' ListPrincipals (Maybe Natural)
listPrincipals_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPrincipals' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListPrincipals' :: ListPrincipals -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListPrincipals
s@ListPrincipals' {} Maybe Natural
a -> ListPrincipals
s {$sel:maxResults:ListPrincipals' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListPrincipals)

-- | Specifies that you want to receive the next page of results. Valid only
-- if you received a @NextToken@ response in the previous request. If you
-- did, it indicates that more output is available. Set this parameter to
-- the value provided by the previous call\'s @NextToken@ response to
-- request the next page of results.
listPrincipals_nextToken :: Lens.Lens' ListPrincipals (Prelude.Maybe Prelude.Text)
listPrincipals_nextToken :: Lens' ListPrincipals (Maybe Text)
listPrincipals_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPrincipals' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListPrincipals' :: ListPrincipals -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListPrincipals
s@ListPrincipals' {} Maybe Text
a -> ListPrincipals
s {$sel:nextToken:ListPrincipals' :: Maybe Text
nextToken = Maybe Text
a} :: ListPrincipals)

-- | Specifies that you want to list information for only the listed
-- principals.
--
-- You can include the following values:
--
-- -   An Amazon Web Services account ID, for example: @123456789012@
--
-- -   An
--     <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
--     of an organization in Organizations, for example:
--     @organizations::123456789012:organization\/o-exampleorgid@
--
-- -   An ARN of an organizational unit (OU) in Organizations, for example:
--     @organizations::123456789012:ou\/o-exampleorgid\/ou-examplerootid-exampleouid123@
--
-- -   An ARN of an IAM role, for example:
--     @iam::123456789012:role\/rolename@
--
-- -   An ARN of an IAM user, for example:
--     @iam::123456789012user\/username@
--
-- Not all resource types can be shared with IAM roles and users. For more
-- information, see
-- <https://docs.aws.amazon.com/ram/latest/userguide/permissions.html#permissions-rbp-supported-resource-types Sharing with IAM roles and users>
-- in the /Resource Access Manager User Guide/.
listPrincipals_principals :: Lens.Lens' ListPrincipals (Prelude.Maybe [Prelude.Text])
listPrincipals_principals :: Lens' ListPrincipals (Maybe [Text])
listPrincipals_principals = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPrincipals' {Maybe [Text]
principals :: Maybe [Text]
$sel:principals:ListPrincipals' :: ListPrincipals -> Maybe [Text]
principals} -> Maybe [Text]
principals) (\s :: ListPrincipals
s@ListPrincipals' {} Maybe [Text]
a -> ListPrincipals
s {$sel:principals:ListPrincipals' :: Maybe [Text]
principals = Maybe [Text]
a} :: ListPrincipals) 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

-- | Specifies that you want to list principal information for the resource
-- share with the specified
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>.
listPrincipals_resourceArn :: Lens.Lens' ListPrincipals (Prelude.Maybe Prelude.Text)
listPrincipals_resourceArn :: Lens' ListPrincipals (Maybe Text)
listPrincipals_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPrincipals' {Maybe Text
resourceArn :: Maybe Text
$sel:resourceArn:ListPrincipals' :: ListPrincipals -> Maybe Text
resourceArn} -> Maybe Text
resourceArn) (\s :: ListPrincipals
s@ListPrincipals' {} Maybe Text
a -> ListPrincipals
s {$sel:resourceArn:ListPrincipals' :: Maybe Text
resourceArn = Maybe Text
a} :: ListPrincipals)

-- | Specifies that you want to list information for only principals
-- associated with the resource shares specified by a list the
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>.
listPrincipals_resourceShareArns :: Lens.Lens' ListPrincipals (Prelude.Maybe [Prelude.Text])
listPrincipals_resourceShareArns :: Lens' ListPrincipals (Maybe [Text])
listPrincipals_resourceShareArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPrincipals' {Maybe [Text]
resourceShareArns :: Maybe [Text]
$sel:resourceShareArns:ListPrincipals' :: ListPrincipals -> Maybe [Text]
resourceShareArns} -> Maybe [Text]
resourceShareArns) (\s :: ListPrincipals
s@ListPrincipals' {} Maybe [Text]
a -> ListPrincipals
s {$sel:resourceShareArns:ListPrincipals' :: Maybe [Text]
resourceShareArns = Maybe [Text]
a} :: ListPrincipals) 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

-- | Specifies that you want to list information for only principals
-- associated with resource shares that include the specified resource
-- type.
--
-- For a list of valid values, query the ListResourceTypes operation.
listPrincipals_resourceType :: Lens.Lens' ListPrincipals (Prelude.Maybe Prelude.Text)
listPrincipals_resourceType :: Lens' ListPrincipals (Maybe Text)
listPrincipals_resourceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPrincipals' {Maybe Text
resourceType :: Maybe Text
$sel:resourceType:ListPrincipals' :: ListPrincipals -> Maybe Text
resourceType} -> Maybe Text
resourceType) (\s :: ListPrincipals
s@ListPrincipals' {} Maybe Text
a -> ListPrincipals
s {$sel:resourceType:ListPrincipals' :: Maybe Text
resourceType = Maybe Text
a} :: ListPrincipals)

-- | Specifies that you want to list information for only resource shares
-- that match the following:
--
-- -   __@SELF@__ – principals that your account is sharing resources with
--
-- -   __@OTHER-ACCOUNTS@__ – principals that are sharing resources with
--     your account
listPrincipals_resourceOwner :: Lens.Lens' ListPrincipals ResourceOwner
listPrincipals_resourceOwner :: Lens' ListPrincipals ResourceOwner
listPrincipals_resourceOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPrincipals' {ResourceOwner
resourceOwner :: ResourceOwner
$sel:resourceOwner:ListPrincipals' :: ListPrincipals -> ResourceOwner
resourceOwner} -> ResourceOwner
resourceOwner) (\s :: ListPrincipals
s@ListPrincipals' {} ResourceOwner
a -> ListPrincipals
s {$sel:resourceOwner:ListPrincipals' :: ResourceOwner
resourceOwner = ResourceOwner
a} :: ListPrincipals)

instance Core.AWSPager ListPrincipals where
  page :: ListPrincipals
-> AWSResponse ListPrincipals -> Maybe ListPrincipals
page ListPrincipals
rq AWSResponse ListPrincipals
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListPrincipals
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListPrincipalsResponse (Maybe Text)
listPrincipalsResponse_nextToken
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListPrincipals
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListPrincipalsResponse (Maybe [Principal])
listPrincipalsResponse_principals
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListPrincipals
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListPrincipals (Maybe Text)
listPrincipals_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListPrincipals
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListPrincipalsResponse (Maybe Text)
listPrincipalsResponse_nextToken
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest ListPrincipals where
  type
    AWSResponse ListPrincipals =
      ListPrincipalsResponse
  request :: (Service -> Service) -> ListPrincipals -> Request ListPrincipals
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 ListPrincipals
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListPrincipals)))
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 Text -> Maybe [Principal] -> Int -> ListPrincipalsResponse
ListPrincipalsResponse'
            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
"nextToken")
            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
"principals" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 ListPrincipals where
  hashWithSalt :: Int -> ListPrincipals -> Int
hashWithSalt Int
_salt ListPrincipals' {Maybe Natural
Maybe [Text]
Maybe Text
ResourceOwner
resourceOwner :: ResourceOwner
resourceType :: Maybe Text
resourceShareArns :: Maybe [Text]
resourceArn :: Maybe Text
principals :: Maybe [Text]
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceOwner:ListPrincipals' :: ListPrincipals -> ResourceOwner
$sel:resourceType:ListPrincipals' :: ListPrincipals -> Maybe Text
$sel:resourceShareArns:ListPrincipals' :: ListPrincipals -> Maybe [Text]
$sel:resourceArn:ListPrincipals' :: ListPrincipals -> Maybe Text
$sel:principals:ListPrincipals' :: ListPrincipals -> Maybe [Text]
$sel:nextToken:ListPrincipals' :: ListPrincipals -> Maybe Text
$sel:maxResults:ListPrincipals' :: ListPrincipals -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
principals
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
resourceShareArns
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ResourceOwner
resourceOwner

instance Prelude.NFData ListPrincipals where
  rnf :: ListPrincipals -> ()
rnf ListPrincipals' {Maybe Natural
Maybe [Text]
Maybe Text
ResourceOwner
resourceOwner :: ResourceOwner
resourceType :: Maybe Text
resourceShareArns :: Maybe [Text]
resourceArn :: Maybe Text
principals :: Maybe [Text]
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceOwner:ListPrincipals' :: ListPrincipals -> ResourceOwner
$sel:resourceType:ListPrincipals' :: ListPrincipals -> Maybe Text
$sel:resourceShareArns:ListPrincipals' :: ListPrincipals -> Maybe [Text]
$sel:resourceArn:ListPrincipals' :: ListPrincipals -> Maybe Text
$sel:principals:ListPrincipals' :: ListPrincipals -> Maybe [Text]
$sel:nextToken:ListPrincipals' :: ListPrincipals -> Maybe Text
$sel:maxResults:ListPrincipals' :: ListPrincipals -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
principals
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
resourceArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
resourceShareArns
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
resourceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ResourceOwner
resourceOwner

instance Data.ToHeaders ListPrincipals where
  toHeaders :: ListPrincipals -> 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.ToJSON ListPrincipals where
  toJSON :: ListPrincipals -> Value
toJSON ListPrincipals' {Maybe Natural
Maybe [Text]
Maybe Text
ResourceOwner
resourceOwner :: ResourceOwner
resourceType :: Maybe Text
resourceShareArns :: Maybe [Text]
resourceArn :: Maybe Text
principals :: Maybe [Text]
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceOwner:ListPrincipals' :: ListPrincipals -> ResourceOwner
$sel:resourceType:ListPrincipals' :: ListPrincipals -> Maybe Text
$sel:resourceShareArns:ListPrincipals' :: ListPrincipals -> Maybe [Text]
$sel:resourceArn:ListPrincipals' :: ListPrincipals -> Maybe Text
$sel:principals:ListPrincipals' :: ListPrincipals -> Maybe [Text]
$sel:nextToken:ListPrincipals' :: ListPrincipals -> Maybe Text
$sel:maxResults:ListPrincipals' :: ListPrincipals -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"maxResults" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
maxResults,
            (Key
"nextToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
nextToken,
            (Key
"principals" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
principals,
            (Key
"resourceArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
resourceArn,
            (Key
"resourceShareArns" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
resourceShareArns,
            (Key
"resourceType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
resourceType,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"resourceOwner" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ResourceOwner
resourceOwner)
          ]
      )

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

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

-- | /See:/ 'newListPrincipalsResponse' smart constructor.
data ListPrincipalsResponse = ListPrincipalsResponse'
  { -- | If present, this value indicates that more output is available than is
    -- included in the current response. Use this value in the @NextToken@
    -- request parameter in a subsequent call to the operation to get the next
    -- part of the output. You should repeat this until the @NextToken@
    -- response element comes back as @null@. This indicates that this is the
    -- last page of results.
    ListPrincipalsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | An array of objects that contain the details about the principals.
    ListPrincipalsResponse -> Maybe [Principal]
principals :: Prelude.Maybe [Principal],
    -- | The response's http status code.
    ListPrincipalsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListPrincipalsResponse -> ListPrincipalsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPrincipalsResponse -> ListPrincipalsResponse -> Bool
$c/= :: ListPrincipalsResponse -> ListPrincipalsResponse -> Bool
== :: ListPrincipalsResponse -> ListPrincipalsResponse -> Bool
$c== :: ListPrincipalsResponse -> ListPrincipalsResponse -> Bool
Prelude.Eq, ReadPrec [ListPrincipalsResponse]
ReadPrec ListPrincipalsResponse
Int -> ReadS ListPrincipalsResponse
ReadS [ListPrincipalsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPrincipalsResponse]
$creadListPrec :: ReadPrec [ListPrincipalsResponse]
readPrec :: ReadPrec ListPrincipalsResponse
$creadPrec :: ReadPrec ListPrincipalsResponse
readList :: ReadS [ListPrincipalsResponse]
$creadList :: ReadS [ListPrincipalsResponse]
readsPrec :: Int -> ReadS ListPrincipalsResponse
$creadsPrec :: Int -> ReadS ListPrincipalsResponse
Prelude.Read, Int -> ListPrincipalsResponse -> ShowS
[ListPrincipalsResponse] -> ShowS
ListPrincipalsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPrincipalsResponse] -> ShowS
$cshowList :: [ListPrincipalsResponse] -> ShowS
show :: ListPrincipalsResponse -> String
$cshow :: ListPrincipalsResponse -> String
showsPrec :: Int -> ListPrincipalsResponse -> ShowS
$cshowsPrec :: Int -> ListPrincipalsResponse -> ShowS
Prelude.Show, forall x. Rep ListPrincipalsResponse x -> ListPrincipalsResponse
forall x. ListPrincipalsResponse -> Rep ListPrincipalsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListPrincipalsResponse x -> ListPrincipalsResponse
$cfrom :: forall x. ListPrincipalsResponse -> Rep ListPrincipalsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListPrincipalsResponse' 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:
--
-- 'nextToken', 'listPrincipalsResponse_nextToken' - If present, this value indicates that more output is available than is
-- included in the current response. Use this value in the @NextToken@
-- request parameter in a subsequent call to the operation to get the next
-- part of the output. You should repeat this until the @NextToken@
-- response element comes back as @null@. This indicates that this is the
-- last page of results.
--
-- 'principals', 'listPrincipalsResponse_principals' - An array of objects that contain the details about the principals.
--
-- 'httpStatus', 'listPrincipalsResponse_httpStatus' - The response's http status code.
newListPrincipalsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListPrincipalsResponse
newListPrincipalsResponse :: Int -> ListPrincipalsResponse
newListPrincipalsResponse Int
pHttpStatus_ =
  ListPrincipalsResponse'
    { $sel:nextToken:ListPrincipalsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:principals:ListPrincipalsResponse' :: Maybe [Principal]
principals = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListPrincipalsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | If present, this value indicates that more output is available than is
-- included in the current response. Use this value in the @NextToken@
-- request parameter in a subsequent call to the operation to get the next
-- part of the output. You should repeat this until the @NextToken@
-- response element comes back as @null@. This indicates that this is the
-- last page of results.
listPrincipalsResponse_nextToken :: Lens.Lens' ListPrincipalsResponse (Prelude.Maybe Prelude.Text)
listPrincipalsResponse_nextToken :: Lens' ListPrincipalsResponse (Maybe Text)
listPrincipalsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPrincipalsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListPrincipalsResponse' :: ListPrincipalsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListPrincipalsResponse
s@ListPrincipalsResponse' {} Maybe Text
a -> ListPrincipalsResponse
s {$sel:nextToken:ListPrincipalsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListPrincipalsResponse)

-- | An array of objects that contain the details about the principals.
listPrincipalsResponse_principals :: Lens.Lens' ListPrincipalsResponse (Prelude.Maybe [Principal])
listPrincipalsResponse_principals :: Lens' ListPrincipalsResponse (Maybe [Principal])
listPrincipalsResponse_principals = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPrincipalsResponse' {Maybe [Principal]
principals :: Maybe [Principal]
$sel:principals:ListPrincipalsResponse' :: ListPrincipalsResponse -> Maybe [Principal]
principals} -> Maybe [Principal]
principals) (\s :: ListPrincipalsResponse
s@ListPrincipalsResponse' {} Maybe [Principal]
a -> ListPrincipalsResponse
s {$sel:principals:ListPrincipalsResponse' :: Maybe [Principal]
principals = Maybe [Principal]
a} :: ListPrincipalsResponse) 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.
listPrincipalsResponse_httpStatus :: Lens.Lens' ListPrincipalsResponse Prelude.Int
listPrincipalsResponse_httpStatus :: Lens' ListPrincipalsResponse Int
listPrincipalsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPrincipalsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListPrincipalsResponse' :: ListPrincipalsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListPrincipalsResponse
s@ListPrincipalsResponse' {} Int
a -> ListPrincipalsResponse
s {$sel:httpStatus:ListPrincipalsResponse' :: Int
httpStatus = Int
a} :: ListPrincipalsResponse)

instance Prelude.NFData ListPrincipalsResponse where
  rnf :: ListPrincipalsResponse -> ()
rnf ListPrincipalsResponse' {Int
Maybe [Principal]
Maybe Text
httpStatus :: Int
principals :: Maybe [Principal]
nextToken :: Maybe Text
$sel:httpStatus:ListPrincipalsResponse' :: ListPrincipalsResponse -> Int
$sel:principals:ListPrincipalsResponse' :: ListPrincipalsResponse -> Maybe [Principal]
$sel:nextToken:ListPrincipalsResponse' :: ListPrincipalsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Principal]
principals
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus