{-# 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.GetResourceShareInvitations
-- 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 details about invitations that you have received for resource
-- shares.
--
-- This operation returns paginated results.
module Amazonka.RAM.GetResourceShareInvitations
  ( -- * Creating a Request
    GetResourceShareInvitations (..),
    newGetResourceShareInvitations,

    -- * Request Lenses
    getResourceShareInvitations_maxResults,
    getResourceShareInvitations_nextToken,
    getResourceShareInvitations_resourceShareArns,
    getResourceShareInvitations_resourceShareInvitationArns,

    -- * Destructuring the Response
    GetResourceShareInvitationsResponse (..),
    newGetResourceShareInvitationsResponse,

    -- * Response Lenses
    getResourceShareInvitationsResponse_nextToken,
    getResourceShareInvitationsResponse_resourceShareInvitations,
    getResourceShareInvitationsResponse_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:/ 'newGetResourceShareInvitations' smart constructor.
data GetResourceShareInvitations = GetResourceShareInvitations'
  { -- | 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.
    GetResourceShareInvitations -> 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.
    GetResourceShareInvitations -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Specifies that you want details about invitations only for the resource
    -- shares described by this list of
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
    GetResourceShareInvitations -> Maybe [Text]
resourceShareArns :: Prelude.Maybe [Prelude.Text],
    -- | Specifies the
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
    -- of the resource share invitations you want information about.
    GetResourceShareInvitations -> Maybe [Text]
resourceShareInvitationArns :: Prelude.Maybe [Prelude.Text]
  }
  deriving (GetResourceShareInvitations -> GetResourceShareInvitations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetResourceShareInvitations -> GetResourceShareInvitations -> Bool
$c/= :: GetResourceShareInvitations -> GetResourceShareInvitations -> Bool
== :: GetResourceShareInvitations -> GetResourceShareInvitations -> Bool
$c== :: GetResourceShareInvitations -> GetResourceShareInvitations -> Bool
Prelude.Eq, ReadPrec [GetResourceShareInvitations]
ReadPrec GetResourceShareInvitations
Int -> ReadS GetResourceShareInvitations
ReadS [GetResourceShareInvitations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetResourceShareInvitations]
$creadListPrec :: ReadPrec [GetResourceShareInvitations]
readPrec :: ReadPrec GetResourceShareInvitations
$creadPrec :: ReadPrec GetResourceShareInvitations
readList :: ReadS [GetResourceShareInvitations]
$creadList :: ReadS [GetResourceShareInvitations]
readsPrec :: Int -> ReadS GetResourceShareInvitations
$creadsPrec :: Int -> ReadS GetResourceShareInvitations
Prelude.Read, Int -> GetResourceShareInvitations -> ShowS
[GetResourceShareInvitations] -> ShowS
GetResourceShareInvitations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetResourceShareInvitations] -> ShowS
$cshowList :: [GetResourceShareInvitations] -> ShowS
show :: GetResourceShareInvitations -> String
$cshow :: GetResourceShareInvitations -> String
showsPrec :: Int -> GetResourceShareInvitations -> ShowS
$cshowsPrec :: Int -> GetResourceShareInvitations -> ShowS
Prelude.Show, forall x.
Rep GetResourceShareInvitations x -> GetResourceShareInvitations
forall x.
GetResourceShareInvitations -> Rep GetResourceShareInvitations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetResourceShareInvitations x -> GetResourceShareInvitations
$cfrom :: forall x.
GetResourceShareInvitations -> Rep GetResourceShareInvitations x
Prelude.Generic)

-- |
-- Create a value of 'GetResourceShareInvitations' 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', 'getResourceShareInvitations_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', 'getResourceShareInvitations_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.
--
-- 'resourceShareArns', 'getResourceShareInvitations_resourceShareArns' - Specifies that you want details about invitations only for the resource
-- shares described by this list of
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
--
-- 'resourceShareInvitationArns', 'getResourceShareInvitations_resourceShareInvitationArns' - Specifies the
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- of the resource share invitations you want information about.
newGetResourceShareInvitations ::
  GetResourceShareInvitations
newGetResourceShareInvitations :: GetResourceShareInvitations
newGetResourceShareInvitations =
  GetResourceShareInvitations'
    { $sel:maxResults:GetResourceShareInvitations' :: Maybe Natural
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetResourceShareInvitations' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceShareArns:GetResourceShareInvitations' :: Maybe [Text]
resourceShareArns = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceShareInvitationArns:GetResourceShareInvitations' :: Maybe [Text]
resourceShareInvitationArns = forall a. Maybe a
Prelude.Nothing
    }

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

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

-- | Specifies that you want details about invitations only for the resource
-- shares described by this list of
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
getResourceShareInvitations_resourceShareArns :: Lens.Lens' GetResourceShareInvitations (Prelude.Maybe [Prelude.Text])
getResourceShareInvitations_resourceShareArns :: Lens' GetResourceShareInvitations (Maybe [Text])
getResourceShareInvitations_resourceShareArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetResourceShareInvitations' {Maybe [Text]
resourceShareArns :: Maybe [Text]
$sel:resourceShareArns:GetResourceShareInvitations' :: GetResourceShareInvitations -> Maybe [Text]
resourceShareArns} -> Maybe [Text]
resourceShareArns) (\s :: GetResourceShareInvitations
s@GetResourceShareInvitations' {} Maybe [Text]
a -> GetResourceShareInvitations
s {$sel:resourceShareArns:GetResourceShareInvitations' :: Maybe [Text]
resourceShareArns = Maybe [Text]
a} :: GetResourceShareInvitations) 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 the
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- of the resource share invitations you want information about.
getResourceShareInvitations_resourceShareInvitationArns :: Lens.Lens' GetResourceShareInvitations (Prelude.Maybe [Prelude.Text])
getResourceShareInvitations_resourceShareInvitationArns :: Lens' GetResourceShareInvitations (Maybe [Text])
getResourceShareInvitations_resourceShareInvitationArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetResourceShareInvitations' {Maybe [Text]
resourceShareInvitationArns :: Maybe [Text]
$sel:resourceShareInvitationArns:GetResourceShareInvitations' :: GetResourceShareInvitations -> Maybe [Text]
resourceShareInvitationArns} -> Maybe [Text]
resourceShareInvitationArns) (\s :: GetResourceShareInvitations
s@GetResourceShareInvitations' {} Maybe [Text]
a -> GetResourceShareInvitations
s {$sel:resourceShareInvitationArns:GetResourceShareInvitations' :: Maybe [Text]
resourceShareInvitationArns = Maybe [Text]
a} :: GetResourceShareInvitations) 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

instance Core.AWSPager GetResourceShareInvitations where
  page :: GetResourceShareInvitations
-> AWSResponse GetResourceShareInvitations
-> Maybe GetResourceShareInvitations
page GetResourceShareInvitations
rq AWSResponse GetResourceShareInvitations
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse GetResourceShareInvitations
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetResourceShareInvitationsResponse (Maybe Text)
getResourceShareInvitationsResponse_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 GetResourceShareInvitations
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  GetResourceShareInvitationsResponse
  (Maybe [ResourceShareInvitation])
getResourceShareInvitationsResponse_resourceShareInvitations
            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.$ GetResourceShareInvitations
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' GetResourceShareInvitations (Maybe Text)
getResourceShareInvitations_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse GetResourceShareInvitations
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetResourceShareInvitationsResponse (Maybe Text)
getResourceShareInvitationsResponse_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 GetResourceShareInvitations where
  type
    AWSResponse GetResourceShareInvitations =
      GetResourceShareInvitationsResponse
  request :: (Service -> Service)
-> GetResourceShareInvitations
-> Request GetResourceShareInvitations
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 GetResourceShareInvitations
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetResourceShareInvitations)))
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 [ResourceShareInvitation]
-> Int
-> GetResourceShareInvitationsResponse
GetResourceShareInvitationsResponse'
            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
"resourceShareInvitations"
                            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 GetResourceShareInvitations where
  hashWithSalt :: Int -> GetResourceShareInvitations -> Int
hashWithSalt Int
_salt GetResourceShareInvitations' {Maybe Natural
Maybe [Text]
Maybe Text
resourceShareInvitationArns :: Maybe [Text]
resourceShareArns :: Maybe [Text]
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceShareInvitationArns:GetResourceShareInvitations' :: GetResourceShareInvitations -> Maybe [Text]
$sel:resourceShareArns:GetResourceShareInvitations' :: GetResourceShareInvitations -> Maybe [Text]
$sel:nextToken:GetResourceShareInvitations' :: GetResourceShareInvitations -> Maybe Text
$sel:maxResults:GetResourceShareInvitations' :: GetResourceShareInvitations -> 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]
resourceShareArns
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
resourceShareInvitationArns

instance Prelude.NFData GetResourceShareInvitations where
  rnf :: GetResourceShareInvitations -> ()
rnf GetResourceShareInvitations' {Maybe Natural
Maybe [Text]
Maybe Text
resourceShareInvitationArns :: Maybe [Text]
resourceShareArns :: Maybe [Text]
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceShareInvitationArns:GetResourceShareInvitations' :: GetResourceShareInvitations -> Maybe [Text]
$sel:resourceShareArns:GetResourceShareInvitations' :: GetResourceShareInvitations -> Maybe [Text]
$sel:nextToken:GetResourceShareInvitations' :: GetResourceShareInvitations -> Maybe Text
$sel:maxResults:GetResourceShareInvitations' :: GetResourceShareInvitations -> 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]
resourceShareArns
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
resourceShareInvitationArns

instance Data.ToHeaders GetResourceShareInvitations where
  toHeaders :: GetResourceShareInvitations -> 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 GetResourceShareInvitations where
  toJSON :: GetResourceShareInvitations -> Value
toJSON GetResourceShareInvitations' {Maybe Natural
Maybe [Text]
Maybe Text
resourceShareInvitationArns :: Maybe [Text]
resourceShareArns :: Maybe [Text]
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceShareInvitationArns:GetResourceShareInvitations' :: GetResourceShareInvitations -> Maybe [Text]
$sel:resourceShareArns:GetResourceShareInvitations' :: GetResourceShareInvitations -> Maybe [Text]
$sel:nextToken:GetResourceShareInvitations' :: GetResourceShareInvitations -> Maybe Text
$sel:maxResults:GetResourceShareInvitations' :: GetResourceShareInvitations -> 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
"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
"resourceShareInvitationArns" 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]
resourceShareInvitationArns
          ]
      )

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

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

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

-- |
-- Create a value of 'GetResourceShareInvitationsResponse' 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', 'getResourceShareInvitationsResponse_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.
--
-- 'resourceShareInvitations', 'getResourceShareInvitationsResponse_resourceShareInvitations' - An array of objects that contain the details about the invitations.
--
-- 'httpStatus', 'getResourceShareInvitationsResponse_httpStatus' - The response's http status code.
newGetResourceShareInvitationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetResourceShareInvitationsResponse
newGetResourceShareInvitationsResponse :: Int -> GetResourceShareInvitationsResponse
newGetResourceShareInvitationsResponse Int
pHttpStatus_ =
  GetResourceShareInvitationsResponse'
    { $sel:nextToken:GetResourceShareInvitationsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:resourceShareInvitations:GetResourceShareInvitationsResponse' :: Maybe [ResourceShareInvitation]
resourceShareInvitations =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetResourceShareInvitationsResponse' :: 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.
getResourceShareInvitationsResponse_nextToken :: Lens.Lens' GetResourceShareInvitationsResponse (Prelude.Maybe Prelude.Text)
getResourceShareInvitationsResponse_nextToken :: Lens' GetResourceShareInvitationsResponse (Maybe Text)
getResourceShareInvitationsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetResourceShareInvitationsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetResourceShareInvitationsResponse' :: GetResourceShareInvitationsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetResourceShareInvitationsResponse
s@GetResourceShareInvitationsResponse' {} Maybe Text
a -> GetResourceShareInvitationsResponse
s {$sel:nextToken:GetResourceShareInvitationsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetResourceShareInvitationsResponse)

-- | An array of objects that contain the details about the invitations.
getResourceShareInvitationsResponse_resourceShareInvitations :: Lens.Lens' GetResourceShareInvitationsResponse (Prelude.Maybe [ResourceShareInvitation])
getResourceShareInvitationsResponse_resourceShareInvitations :: Lens'
  GetResourceShareInvitationsResponse
  (Maybe [ResourceShareInvitation])
getResourceShareInvitationsResponse_resourceShareInvitations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetResourceShareInvitationsResponse' {Maybe [ResourceShareInvitation]
resourceShareInvitations :: Maybe [ResourceShareInvitation]
$sel:resourceShareInvitations:GetResourceShareInvitationsResponse' :: GetResourceShareInvitationsResponse
-> Maybe [ResourceShareInvitation]
resourceShareInvitations} -> Maybe [ResourceShareInvitation]
resourceShareInvitations) (\s :: GetResourceShareInvitationsResponse
s@GetResourceShareInvitationsResponse' {} Maybe [ResourceShareInvitation]
a -> GetResourceShareInvitationsResponse
s {$sel:resourceShareInvitations:GetResourceShareInvitationsResponse' :: Maybe [ResourceShareInvitation]
resourceShareInvitations = Maybe [ResourceShareInvitation]
a} :: GetResourceShareInvitationsResponse) 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.
getResourceShareInvitationsResponse_httpStatus :: Lens.Lens' GetResourceShareInvitationsResponse Prelude.Int
getResourceShareInvitationsResponse_httpStatus :: Lens' GetResourceShareInvitationsResponse Int
getResourceShareInvitationsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetResourceShareInvitationsResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetResourceShareInvitationsResponse' :: GetResourceShareInvitationsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetResourceShareInvitationsResponse
s@GetResourceShareInvitationsResponse' {} Int
a -> GetResourceShareInvitationsResponse
s {$sel:httpStatus:GetResourceShareInvitationsResponse' :: Int
httpStatus = Int
a} :: GetResourceShareInvitationsResponse)

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