{-# 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.ListPendingInvitationResources
-- 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 resources in a resource share that is shared with you but for
-- which the invitation is still @PENDING@. That means that you haven\'t
-- accepted or rejected the invitation and the invitation hasn\'t expired.
module Amazonka.RAM.ListPendingInvitationResources
  ( -- * Creating a Request
    ListPendingInvitationResources (..),
    newListPendingInvitationResources,

    -- * Request Lenses
    listPendingInvitationResources_maxResults,
    listPendingInvitationResources_nextToken,
    listPendingInvitationResources_resourceRegionScope,
    listPendingInvitationResources_resourceShareInvitationArn,

    -- * Destructuring the Response
    ListPendingInvitationResourcesResponse (..),
    newListPendingInvitationResourcesResponse,

    -- * Response Lenses
    listPendingInvitationResourcesResponse_nextToken,
    listPendingInvitationResourcesResponse_resources,
    listPendingInvitationResourcesResponse_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:/ 'newListPendingInvitationResources' smart constructor.
data ListPendingInvitationResources = ListPendingInvitationResources'
  { -- | 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.
    ListPendingInvitationResources -> 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.
    ListPendingInvitationResources -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Specifies that you want the results to include only resources that have
    -- the specified scope.
    --
    -- -   @ALL@ – the results include both global and regional resources or
    --     resource types.
    --
    -- -   @GLOBAL@ – the results include only global resources or resource
    --     types.
    --
    -- -   @REGIONAL@ – the results include only regional resources or resource
    --     types.
    --
    -- The default value is @ALL@.
    ListPendingInvitationResources -> Maybe ResourceRegionScopeFilter
resourceRegionScope :: Prelude.Maybe ResourceRegionScopeFilter,
    -- | Specifies the
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
    -- of the invitation. You can use GetResourceShareInvitations to find the
    -- ARN of the invitation.
    ListPendingInvitationResources -> Text
resourceShareInvitationArn :: Prelude.Text
  }
  deriving (ListPendingInvitationResources
-> ListPendingInvitationResources -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPendingInvitationResources
-> ListPendingInvitationResources -> Bool
$c/= :: ListPendingInvitationResources
-> ListPendingInvitationResources -> Bool
== :: ListPendingInvitationResources
-> ListPendingInvitationResources -> Bool
$c== :: ListPendingInvitationResources
-> ListPendingInvitationResources -> Bool
Prelude.Eq, ReadPrec [ListPendingInvitationResources]
ReadPrec ListPendingInvitationResources
Int -> ReadS ListPendingInvitationResources
ReadS [ListPendingInvitationResources]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPendingInvitationResources]
$creadListPrec :: ReadPrec [ListPendingInvitationResources]
readPrec :: ReadPrec ListPendingInvitationResources
$creadPrec :: ReadPrec ListPendingInvitationResources
readList :: ReadS [ListPendingInvitationResources]
$creadList :: ReadS [ListPendingInvitationResources]
readsPrec :: Int -> ReadS ListPendingInvitationResources
$creadsPrec :: Int -> ReadS ListPendingInvitationResources
Prelude.Read, Int -> ListPendingInvitationResources -> ShowS
[ListPendingInvitationResources] -> ShowS
ListPendingInvitationResources -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPendingInvitationResources] -> ShowS
$cshowList :: [ListPendingInvitationResources] -> ShowS
show :: ListPendingInvitationResources -> String
$cshow :: ListPendingInvitationResources -> String
showsPrec :: Int -> ListPendingInvitationResources -> ShowS
$cshowsPrec :: Int -> ListPendingInvitationResources -> ShowS
Prelude.Show, forall x.
Rep ListPendingInvitationResources x
-> ListPendingInvitationResources
forall x.
ListPendingInvitationResources
-> Rep ListPendingInvitationResources x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListPendingInvitationResources x
-> ListPendingInvitationResources
$cfrom :: forall x.
ListPendingInvitationResources
-> Rep ListPendingInvitationResources x
Prelude.Generic)

-- |
-- Create a value of 'ListPendingInvitationResources' 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', 'listPendingInvitationResources_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', 'listPendingInvitationResources_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.
--
-- 'resourceRegionScope', 'listPendingInvitationResources_resourceRegionScope' - Specifies that you want the results to include only resources that have
-- the specified scope.
--
-- -   @ALL@ – the results include both global and regional resources or
--     resource types.
--
-- -   @GLOBAL@ – the results include only global resources or resource
--     types.
--
-- -   @REGIONAL@ – the results include only regional resources or resource
--     types.
--
-- The default value is @ALL@.
--
-- 'resourceShareInvitationArn', 'listPendingInvitationResources_resourceShareInvitationArn' - Specifies the
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
-- of the invitation. You can use GetResourceShareInvitations to find the
-- ARN of the invitation.
newListPendingInvitationResources ::
  -- | 'resourceShareInvitationArn'
  Prelude.Text ->
  ListPendingInvitationResources
newListPendingInvitationResources :: Text -> ListPendingInvitationResources
newListPendingInvitationResources
  Text
pResourceShareInvitationArn_ =
    ListPendingInvitationResources'
      { $sel:maxResults:ListPendingInvitationResources' :: Maybe Natural
maxResults =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:ListPendingInvitationResources' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:resourceRegionScope:ListPendingInvitationResources' :: Maybe ResourceRegionScopeFilter
resourceRegionScope = forall a. Maybe a
Prelude.Nothing,
        $sel:resourceShareInvitationArn:ListPendingInvitationResources' :: Text
resourceShareInvitationArn =
          Text
pResourceShareInvitationArn_
      }

-- | 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.
listPendingInvitationResources_maxResults :: Lens.Lens' ListPendingInvitationResources (Prelude.Maybe Prelude.Natural)
listPendingInvitationResources_maxResults :: Lens' ListPendingInvitationResources (Maybe Natural)
listPendingInvitationResources_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPendingInvitationResources' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListPendingInvitationResources' :: ListPendingInvitationResources -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListPendingInvitationResources
s@ListPendingInvitationResources' {} Maybe Natural
a -> ListPendingInvitationResources
s {$sel:maxResults:ListPendingInvitationResources' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListPendingInvitationResources)

-- | 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.
listPendingInvitationResources_nextToken :: Lens.Lens' ListPendingInvitationResources (Prelude.Maybe Prelude.Text)
listPendingInvitationResources_nextToken :: Lens' ListPendingInvitationResources (Maybe Text)
listPendingInvitationResources_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPendingInvitationResources' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListPendingInvitationResources' :: ListPendingInvitationResources -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListPendingInvitationResources
s@ListPendingInvitationResources' {} Maybe Text
a -> ListPendingInvitationResources
s {$sel:nextToken:ListPendingInvitationResources' :: Maybe Text
nextToken = Maybe Text
a} :: ListPendingInvitationResources)

-- | Specifies that you want the results to include only resources that have
-- the specified scope.
--
-- -   @ALL@ – the results include both global and regional resources or
--     resource types.
--
-- -   @GLOBAL@ – the results include only global resources or resource
--     types.
--
-- -   @REGIONAL@ – the results include only regional resources or resource
--     types.
--
-- The default value is @ALL@.
listPendingInvitationResources_resourceRegionScope :: Lens.Lens' ListPendingInvitationResources (Prelude.Maybe ResourceRegionScopeFilter)
listPendingInvitationResources_resourceRegionScope :: Lens'
  ListPendingInvitationResources (Maybe ResourceRegionScopeFilter)
listPendingInvitationResources_resourceRegionScope = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPendingInvitationResources' {Maybe ResourceRegionScopeFilter
resourceRegionScope :: Maybe ResourceRegionScopeFilter
$sel:resourceRegionScope:ListPendingInvitationResources' :: ListPendingInvitationResources -> Maybe ResourceRegionScopeFilter
resourceRegionScope} -> Maybe ResourceRegionScopeFilter
resourceRegionScope) (\s :: ListPendingInvitationResources
s@ListPendingInvitationResources' {} Maybe ResourceRegionScopeFilter
a -> ListPendingInvitationResources
s {$sel:resourceRegionScope:ListPendingInvitationResources' :: Maybe ResourceRegionScopeFilter
resourceRegionScope = Maybe ResourceRegionScopeFilter
a} :: ListPendingInvitationResources)

-- | Specifies the
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
-- of the invitation. You can use GetResourceShareInvitations to find the
-- ARN of the invitation.
listPendingInvitationResources_resourceShareInvitationArn :: Lens.Lens' ListPendingInvitationResources Prelude.Text
listPendingInvitationResources_resourceShareInvitationArn :: Lens' ListPendingInvitationResources Text
listPendingInvitationResources_resourceShareInvitationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPendingInvitationResources' {Text
resourceShareInvitationArn :: Text
$sel:resourceShareInvitationArn:ListPendingInvitationResources' :: ListPendingInvitationResources -> Text
resourceShareInvitationArn} -> Text
resourceShareInvitationArn) (\s :: ListPendingInvitationResources
s@ListPendingInvitationResources' {} Text
a -> ListPendingInvitationResources
s {$sel:resourceShareInvitationArn:ListPendingInvitationResources' :: Text
resourceShareInvitationArn = Text
a} :: ListPendingInvitationResources)

instance
  Core.AWSRequest
    ListPendingInvitationResources
  where
  type
    AWSResponse ListPendingInvitationResources =
      ListPendingInvitationResourcesResponse
  request :: (Service -> Service)
-> ListPendingInvitationResources
-> Request ListPendingInvitationResources
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 ListPendingInvitationResources
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse ListPendingInvitationResources)))
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 [Resource]
-> Int
-> ListPendingInvitationResourcesResponse
ListPendingInvitationResourcesResponse'
            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
"resources" 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
    ListPendingInvitationResources
  where
  hashWithSalt :: Int -> ListPendingInvitationResources -> Int
hashWithSalt
    Int
_salt
    ListPendingInvitationResources' {Maybe Natural
Maybe Text
Maybe ResourceRegionScopeFilter
Text
resourceShareInvitationArn :: Text
resourceRegionScope :: Maybe ResourceRegionScopeFilter
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceShareInvitationArn:ListPendingInvitationResources' :: ListPendingInvitationResources -> Text
$sel:resourceRegionScope:ListPendingInvitationResources' :: ListPendingInvitationResources -> Maybe ResourceRegionScopeFilter
$sel:nextToken:ListPendingInvitationResources' :: ListPendingInvitationResources -> Maybe Text
$sel:maxResults:ListPendingInvitationResources' :: ListPendingInvitationResources -> 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 ResourceRegionScopeFilter
resourceRegionScope
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceShareInvitationArn

instance
  Prelude.NFData
    ListPendingInvitationResources
  where
  rnf :: ListPendingInvitationResources -> ()
rnf ListPendingInvitationResources' {Maybe Natural
Maybe Text
Maybe ResourceRegionScopeFilter
Text
resourceShareInvitationArn :: Text
resourceRegionScope :: Maybe ResourceRegionScopeFilter
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceShareInvitationArn:ListPendingInvitationResources' :: ListPendingInvitationResources -> Text
$sel:resourceRegionScope:ListPendingInvitationResources' :: ListPendingInvitationResources -> Maybe ResourceRegionScopeFilter
$sel:nextToken:ListPendingInvitationResources' :: ListPendingInvitationResources -> Maybe Text
$sel:maxResults:ListPendingInvitationResources' :: ListPendingInvitationResources -> 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 ResourceRegionScopeFilter
resourceRegionScope
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
resourceShareInvitationArn

instance
  Data.ToHeaders
    ListPendingInvitationResources
  where
  toHeaders :: ListPendingInvitationResources -> 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 ListPendingInvitationResources where
  toJSON :: ListPendingInvitationResources -> Value
toJSON ListPendingInvitationResources' {Maybe Natural
Maybe Text
Maybe ResourceRegionScopeFilter
Text
resourceShareInvitationArn :: Text
resourceRegionScope :: Maybe ResourceRegionScopeFilter
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceShareInvitationArn:ListPendingInvitationResources' :: ListPendingInvitationResources -> Text
$sel:resourceRegionScope:ListPendingInvitationResources' :: ListPendingInvitationResources -> Maybe ResourceRegionScopeFilter
$sel:nextToken:ListPendingInvitationResources' :: ListPendingInvitationResources -> Maybe Text
$sel:maxResults:ListPendingInvitationResources' :: ListPendingInvitationResources -> 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
"resourceRegionScope" 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 ResourceRegionScopeFilter
resourceRegionScope,
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"resourceShareInvitationArn"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
resourceShareInvitationArn
              )
          ]
      )

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

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

-- | /See:/ 'newListPendingInvitationResourcesResponse' smart constructor.
data ListPendingInvitationResourcesResponse = ListPendingInvitationResourcesResponse'
  { -- | 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.
    ListPendingInvitationResourcesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | An array of objects that contain the information about the resources
    -- included the specified resource share.
    ListPendingInvitationResourcesResponse -> Maybe [Resource]
resources :: Prelude.Maybe [Resource],
    -- | The response's http status code.
    ListPendingInvitationResourcesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListPendingInvitationResourcesResponse
-> ListPendingInvitationResourcesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPendingInvitationResourcesResponse
-> ListPendingInvitationResourcesResponse -> Bool
$c/= :: ListPendingInvitationResourcesResponse
-> ListPendingInvitationResourcesResponse -> Bool
== :: ListPendingInvitationResourcesResponse
-> ListPendingInvitationResourcesResponse -> Bool
$c== :: ListPendingInvitationResourcesResponse
-> ListPendingInvitationResourcesResponse -> Bool
Prelude.Eq, ReadPrec [ListPendingInvitationResourcesResponse]
ReadPrec ListPendingInvitationResourcesResponse
Int -> ReadS ListPendingInvitationResourcesResponse
ReadS [ListPendingInvitationResourcesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPendingInvitationResourcesResponse]
$creadListPrec :: ReadPrec [ListPendingInvitationResourcesResponse]
readPrec :: ReadPrec ListPendingInvitationResourcesResponse
$creadPrec :: ReadPrec ListPendingInvitationResourcesResponse
readList :: ReadS [ListPendingInvitationResourcesResponse]
$creadList :: ReadS [ListPendingInvitationResourcesResponse]
readsPrec :: Int -> ReadS ListPendingInvitationResourcesResponse
$creadsPrec :: Int -> ReadS ListPendingInvitationResourcesResponse
Prelude.Read, Int -> ListPendingInvitationResourcesResponse -> ShowS
[ListPendingInvitationResourcesResponse] -> ShowS
ListPendingInvitationResourcesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPendingInvitationResourcesResponse] -> ShowS
$cshowList :: [ListPendingInvitationResourcesResponse] -> ShowS
show :: ListPendingInvitationResourcesResponse -> String
$cshow :: ListPendingInvitationResourcesResponse -> String
showsPrec :: Int -> ListPendingInvitationResourcesResponse -> ShowS
$cshowsPrec :: Int -> ListPendingInvitationResourcesResponse -> ShowS
Prelude.Show, forall x.
Rep ListPendingInvitationResourcesResponse x
-> ListPendingInvitationResourcesResponse
forall x.
ListPendingInvitationResourcesResponse
-> Rep ListPendingInvitationResourcesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListPendingInvitationResourcesResponse x
-> ListPendingInvitationResourcesResponse
$cfrom :: forall x.
ListPendingInvitationResourcesResponse
-> Rep ListPendingInvitationResourcesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListPendingInvitationResourcesResponse' 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', 'listPendingInvitationResourcesResponse_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.
--
-- 'resources', 'listPendingInvitationResourcesResponse_resources' - An array of objects that contain the information about the resources
-- included the specified resource share.
--
-- 'httpStatus', 'listPendingInvitationResourcesResponse_httpStatus' - The response's http status code.
newListPendingInvitationResourcesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListPendingInvitationResourcesResponse
newListPendingInvitationResourcesResponse :: Int -> ListPendingInvitationResourcesResponse
newListPendingInvitationResourcesResponse
  Int
pHttpStatus_ =
    ListPendingInvitationResourcesResponse'
      { $sel:nextToken:ListPendingInvitationResourcesResponse' :: Maybe Text
nextToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:resources:ListPendingInvitationResourcesResponse' :: Maybe [Resource]
resources = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:ListPendingInvitationResourcesResponse' :: 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.
listPendingInvitationResourcesResponse_nextToken :: Lens.Lens' ListPendingInvitationResourcesResponse (Prelude.Maybe Prelude.Text)
listPendingInvitationResourcesResponse_nextToken :: Lens' ListPendingInvitationResourcesResponse (Maybe Text)
listPendingInvitationResourcesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPendingInvitationResourcesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListPendingInvitationResourcesResponse' :: ListPendingInvitationResourcesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListPendingInvitationResourcesResponse
s@ListPendingInvitationResourcesResponse' {} Maybe Text
a -> ListPendingInvitationResourcesResponse
s {$sel:nextToken:ListPendingInvitationResourcesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListPendingInvitationResourcesResponse)

-- | An array of objects that contain the information about the resources
-- included the specified resource share.
listPendingInvitationResourcesResponse_resources :: Lens.Lens' ListPendingInvitationResourcesResponse (Prelude.Maybe [Resource])
listPendingInvitationResourcesResponse_resources :: Lens' ListPendingInvitationResourcesResponse (Maybe [Resource])
listPendingInvitationResourcesResponse_resources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPendingInvitationResourcesResponse' {Maybe [Resource]
resources :: Maybe [Resource]
$sel:resources:ListPendingInvitationResourcesResponse' :: ListPendingInvitationResourcesResponse -> Maybe [Resource]
resources} -> Maybe [Resource]
resources) (\s :: ListPendingInvitationResourcesResponse
s@ListPendingInvitationResourcesResponse' {} Maybe [Resource]
a -> ListPendingInvitationResourcesResponse
s {$sel:resources:ListPendingInvitationResourcesResponse' :: Maybe [Resource]
resources = Maybe [Resource]
a} :: ListPendingInvitationResourcesResponse) 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.
listPendingInvitationResourcesResponse_httpStatus :: Lens.Lens' ListPendingInvitationResourcesResponse Prelude.Int
listPendingInvitationResourcesResponse_httpStatus :: Lens' ListPendingInvitationResourcesResponse Int
listPendingInvitationResourcesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPendingInvitationResourcesResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListPendingInvitationResourcesResponse' :: ListPendingInvitationResourcesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListPendingInvitationResourcesResponse
s@ListPendingInvitationResourcesResponse' {} Int
a -> ListPendingInvitationResourcesResponse
s {$sel:httpStatus:ListPendingInvitationResourcesResponse' :: Int
httpStatus = Int
a} :: ListPendingInvitationResourcesResponse)

instance
  Prelude.NFData
    ListPendingInvitationResourcesResponse
  where
  rnf :: ListPendingInvitationResourcesResponse -> ()
rnf ListPendingInvitationResourcesResponse' {Int
Maybe [Resource]
Maybe Text
httpStatus :: Int
resources :: Maybe [Resource]
nextToken :: Maybe Text
$sel:httpStatus:ListPendingInvitationResourcesResponse' :: ListPendingInvitationResourcesResponse -> Int
$sel:resources:ListPendingInvitationResourcesResponse' :: ListPendingInvitationResourcesResponse -> Maybe [Resource]
$sel:nextToken:ListPendingInvitationResourcesResponse' :: ListPendingInvitationResourcesResponse -> 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 [Resource]
resources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus