{-# 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.GuardDuty.ListInvitations
-- 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 all GuardDuty membership invitations that were sent to the current
-- Amazon Web Services account.
--
-- This operation returns paginated results.
module Amazonka.GuardDuty.ListInvitations
  ( -- * Creating a Request
    ListInvitations (..),
    newListInvitations,

    -- * Request Lenses
    listInvitations_maxResults,
    listInvitations_nextToken,

    -- * Destructuring the Response
    ListInvitationsResponse (..),
    newListInvitationsResponse,

    -- * Response Lenses
    listInvitationsResponse_invitations,
    listInvitationsResponse_nextToken,
    listInvitationsResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.GuardDuty.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newListInvitations' smart constructor.
data ListInvitations = ListInvitations'
  { -- | You can use this parameter to indicate the maximum number of items that
    -- you want in the response. The default value is 50. The maximum value is
    -- 50.
    ListInvitations -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | You can use this parameter when paginating results. Set the value of
    -- this parameter to null on your first call to the list action. For
    -- subsequent calls to the action, fill nextToken in the request with the
    -- value of NextToken from the previous response to continue listing data.
    ListInvitations -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListInvitations -> ListInvitations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListInvitations -> ListInvitations -> Bool
$c/= :: ListInvitations -> ListInvitations -> Bool
== :: ListInvitations -> ListInvitations -> Bool
$c== :: ListInvitations -> ListInvitations -> Bool
Prelude.Eq, ReadPrec [ListInvitations]
ReadPrec ListInvitations
Int -> ReadS ListInvitations
ReadS [ListInvitations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListInvitations]
$creadListPrec :: ReadPrec [ListInvitations]
readPrec :: ReadPrec ListInvitations
$creadPrec :: ReadPrec ListInvitations
readList :: ReadS [ListInvitations]
$creadList :: ReadS [ListInvitations]
readsPrec :: Int -> ReadS ListInvitations
$creadsPrec :: Int -> ReadS ListInvitations
Prelude.Read, Int -> ListInvitations -> ShowS
[ListInvitations] -> ShowS
ListInvitations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListInvitations] -> ShowS
$cshowList :: [ListInvitations] -> ShowS
show :: ListInvitations -> String
$cshow :: ListInvitations -> String
showsPrec :: Int -> ListInvitations -> ShowS
$cshowsPrec :: Int -> ListInvitations -> ShowS
Prelude.Show, forall x. Rep ListInvitations x -> ListInvitations
forall x. ListInvitations -> Rep ListInvitations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListInvitations x -> ListInvitations
$cfrom :: forall x. ListInvitations -> Rep ListInvitations x
Prelude.Generic)

-- |
-- Create a value of 'ListInvitations' 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', 'listInvitations_maxResults' - You can use this parameter to indicate the maximum number of items that
-- you want in the response. The default value is 50. The maximum value is
-- 50.
--
-- 'nextToken', 'listInvitations_nextToken' - You can use this parameter when paginating results. Set the value of
-- this parameter to null on your first call to the list action. For
-- subsequent calls to the action, fill nextToken in the request with the
-- value of NextToken from the previous response to continue listing data.
newListInvitations ::
  ListInvitations
newListInvitations :: ListInvitations
newListInvitations =
  ListInvitations'
    { $sel:maxResults:ListInvitations' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListInvitations' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | You can use this parameter to indicate the maximum number of items that
-- you want in the response. The default value is 50. The maximum value is
-- 50.
listInvitations_maxResults :: Lens.Lens' ListInvitations (Prelude.Maybe Prelude.Natural)
listInvitations_maxResults :: Lens' ListInvitations (Maybe Natural)
listInvitations_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListInvitations' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListInvitations' :: ListInvitations -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListInvitations
s@ListInvitations' {} Maybe Natural
a -> ListInvitations
s {$sel:maxResults:ListInvitations' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListInvitations)

-- | You can use this parameter when paginating results. Set the value of
-- this parameter to null on your first call to the list action. For
-- subsequent calls to the action, fill nextToken in the request with the
-- value of NextToken from the previous response to continue listing data.
listInvitations_nextToken :: Lens.Lens' ListInvitations (Prelude.Maybe Prelude.Text)
listInvitations_nextToken :: Lens' ListInvitations (Maybe Text)
listInvitations_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListInvitations' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListInvitations' :: ListInvitations -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListInvitations
s@ListInvitations' {} Maybe Text
a -> ListInvitations
s {$sel:nextToken:ListInvitations' :: Maybe Text
nextToken = Maybe Text
a} :: ListInvitations)

instance Core.AWSPager ListInvitations where
  page :: ListInvitations
-> AWSResponse ListInvitations -> Maybe ListInvitations
page ListInvitations
rq AWSResponse ListInvitations
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListInvitations
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListInvitationsResponse (Maybe Text)
listInvitationsResponse_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 ListInvitations
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListInvitationsResponse (Maybe [Invitation])
listInvitationsResponse_invitations
            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.$ ListInvitations
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListInvitations (Maybe Text)
listInvitations_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListInvitations
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListInvitationsResponse (Maybe Text)
listInvitationsResponse_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 ListInvitations where
  type
    AWSResponse ListInvitations =
      ListInvitationsResponse
  request :: (Service -> Service) -> ListInvitations -> Request ListInvitations
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListInvitations
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListInvitations)))
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 [Invitation] -> Maybe Text -> Int -> ListInvitationsResponse
ListInvitationsResponse'
            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
"invitations" 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.<*> (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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable ListInvitations where
  hashWithSalt :: Int -> ListInvitations -> Int
hashWithSalt Int
_salt ListInvitations' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListInvitations' :: ListInvitations -> Maybe Text
$sel:maxResults:ListInvitations' :: ListInvitations -> 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

instance Prelude.NFData ListInvitations where
  rnf :: ListInvitations -> ()
rnf ListInvitations' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListInvitations' :: ListInvitations -> Maybe Text
$sel:maxResults:ListInvitations' :: ListInvitations -> 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

instance Data.ToHeaders ListInvitations where
  toHeaders :: ListInvitations -> 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.ToPath ListInvitations where
  toPath :: ListInvitations -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/invitation"

instance Data.ToQuery ListInvitations where
  toQuery :: ListInvitations -> QueryString
toQuery ListInvitations' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListInvitations' :: ListInvitations -> Maybe Text
$sel:maxResults:ListInvitations' :: ListInvitations -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"maxResults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxResults,
        ByteString
"nextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken
      ]

-- | /See:/ 'newListInvitationsResponse' smart constructor.
data ListInvitationsResponse = ListInvitationsResponse'
  { -- | A list of invitation descriptions.
    ListInvitationsResponse -> Maybe [Invitation]
invitations :: Prelude.Maybe [Invitation],
    -- | The pagination parameter to be used on the next list operation to
    -- retrieve more items.
    ListInvitationsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListInvitationsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListInvitationsResponse -> ListInvitationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListInvitationsResponse -> ListInvitationsResponse -> Bool
$c/= :: ListInvitationsResponse -> ListInvitationsResponse -> Bool
== :: ListInvitationsResponse -> ListInvitationsResponse -> Bool
$c== :: ListInvitationsResponse -> ListInvitationsResponse -> Bool
Prelude.Eq, ReadPrec [ListInvitationsResponse]
ReadPrec ListInvitationsResponse
Int -> ReadS ListInvitationsResponse
ReadS [ListInvitationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListInvitationsResponse]
$creadListPrec :: ReadPrec [ListInvitationsResponse]
readPrec :: ReadPrec ListInvitationsResponse
$creadPrec :: ReadPrec ListInvitationsResponse
readList :: ReadS [ListInvitationsResponse]
$creadList :: ReadS [ListInvitationsResponse]
readsPrec :: Int -> ReadS ListInvitationsResponse
$creadsPrec :: Int -> ReadS ListInvitationsResponse
Prelude.Read, Int -> ListInvitationsResponse -> ShowS
[ListInvitationsResponse] -> ShowS
ListInvitationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListInvitationsResponse] -> ShowS
$cshowList :: [ListInvitationsResponse] -> ShowS
show :: ListInvitationsResponse -> String
$cshow :: ListInvitationsResponse -> String
showsPrec :: Int -> ListInvitationsResponse -> ShowS
$cshowsPrec :: Int -> ListInvitationsResponse -> ShowS
Prelude.Show, forall x. Rep ListInvitationsResponse x -> ListInvitationsResponse
forall x. ListInvitationsResponse -> Rep ListInvitationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListInvitationsResponse x -> ListInvitationsResponse
$cfrom :: forall x. ListInvitationsResponse -> Rep ListInvitationsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListInvitationsResponse' 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:
--
-- 'invitations', 'listInvitationsResponse_invitations' - A list of invitation descriptions.
--
-- 'nextToken', 'listInvitationsResponse_nextToken' - The pagination parameter to be used on the next list operation to
-- retrieve more items.
--
-- 'httpStatus', 'listInvitationsResponse_httpStatus' - The response's http status code.
newListInvitationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListInvitationsResponse
newListInvitationsResponse :: Int -> ListInvitationsResponse
newListInvitationsResponse Int
pHttpStatus_ =
  ListInvitationsResponse'
    { $sel:invitations:ListInvitationsResponse' :: Maybe [Invitation]
invitations =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListInvitationsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListInvitationsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of invitation descriptions.
listInvitationsResponse_invitations :: Lens.Lens' ListInvitationsResponse (Prelude.Maybe [Invitation])
listInvitationsResponse_invitations :: Lens' ListInvitationsResponse (Maybe [Invitation])
listInvitationsResponse_invitations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListInvitationsResponse' {Maybe [Invitation]
invitations :: Maybe [Invitation]
$sel:invitations:ListInvitationsResponse' :: ListInvitationsResponse -> Maybe [Invitation]
invitations} -> Maybe [Invitation]
invitations) (\s :: ListInvitationsResponse
s@ListInvitationsResponse' {} Maybe [Invitation]
a -> ListInvitationsResponse
s {$sel:invitations:ListInvitationsResponse' :: Maybe [Invitation]
invitations = Maybe [Invitation]
a} :: ListInvitationsResponse) 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 pagination parameter to be used on the next list operation to
-- retrieve more items.
listInvitationsResponse_nextToken :: Lens.Lens' ListInvitationsResponse (Prelude.Maybe Prelude.Text)
listInvitationsResponse_nextToken :: Lens' ListInvitationsResponse (Maybe Text)
listInvitationsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListInvitationsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListInvitationsResponse' :: ListInvitationsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListInvitationsResponse
s@ListInvitationsResponse' {} Maybe Text
a -> ListInvitationsResponse
s {$sel:nextToken:ListInvitationsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListInvitationsResponse)

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

instance Prelude.NFData ListInvitationsResponse where
  rnf :: ListInvitationsResponse -> ()
rnf ListInvitationsResponse' {Int
Maybe [Invitation]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
invitations :: Maybe [Invitation]
$sel:httpStatus:ListInvitationsResponse' :: ListInvitationsResponse -> Int
$sel:nextToken:ListInvitationsResponse' :: ListInvitationsResponse -> Maybe Text
$sel:invitations:ListInvitationsResponse' :: ListInvitationsResponse -> Maybe [Invitation]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Invitation]
invitations
      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 Int
httpStatus