{-# 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.ListResources
-- 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 that you added to a resource share or the resources
-- that are shared with you.
--
-- This operation returns paginated results.
module Amazonka.RAM.ListResources
  ( -- * Creating a Request
    ListResources (..),
    newListResources,

    -- * Request Lenses
    listResources_maxResults,
    listResources_nextToken,
    listResources_principal,
    listResources_resourceArns,
    listResources_resourceRegionScope,
    listResources_resourceShareArns,
    listResources_resourceType,
    listResources_resourceOwner,

    -- * Destructuring the Response
    ListResourcesResponse (..),
    newListResourcesResponse,

    -- * Response Lenses
    listResourcesResponse_nextToken,
    listResourcesResponse_resources,
    listResourcesResponse_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:/ 'newListResources' smart constructor.
data ListResources = ListResources'
  { -- | 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.
    ListResources -> 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.
    ListResources -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Specifies that you want to list only the resource shares that are
    -- associated with the specified principal.
    ListResources -> Maybe Text
principal :: Prelude.Maybe Prelude.Text,
    -- | Specifies that you want to list only the resource shares that include
    -- resources with the specified
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>.
    ListResources -> Maybe [Text]
resourceArns :: 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@.
    ListResources -> Maybe ResourceRegionScopeFilter
resourceRegionScope :: Prelude.Maybe ResourceRegionScopeFilter,
    -- | Specifies that you want to list only resources in the resource shares
    -- identified by the specified
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>.
    ListResources -> Maybe [Text]
resourceShareArns :: Prelude.Maybe [Prelude.Text],
    -- | Specifies that you want to list only the resource shares that include
    -- resources of the specified resource type.
    --
    -- For valid values, query the ListResourceTypes operation.
    ListResources -> Maybe Text
resourceType :: Prelude.Maybe Prelude.Text,
    -- | Specifies that you want to list only the resource shares that match the
    -- following:
    --
    -- -   __@SELF@__ – resources that your account shares with other accounts
    --
    -- -   __@OTHER-ACCOUNTS@__ – resources that other accounts share with your
    --     account
    ListResources -> ResourceOwner
resourceOwner :: ResourceOwner
  }
  deriving (ListResources -> ListResources -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListResources -> ListResources -> Bool
$c/= :: ListResources -> ListResources -> Bool
== :: ListResources -> ListResources -> Bool
$c== :: ListResources -> ListResources -> Bool
Prelude.Eq, ReadPrec [ListResources]
ReadPrec ListResources
Int -> ReadS ListResources
ReadS [ListResources]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListResources]
$creadListPrec :: ReadPrec [ListResources]
readPrec :: ReadPrec ListResources
$creadPrec :: ReadPrec ListResources
readList :: ReadS [ListResources]
$creadList :: ReadS [ListResources]
readsPrec :: Int -> ReadS ListResources
$creadsPrec :: Int -> ReadS ListResources
Prelude.Read, Int -> ListResources -> ShowS
[ListResources] -> ShowS
ListResources -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListResources] -> ShowS
$cshowList :: [ListResources] -> ShowS
show :: ListResources -> String
$cshow :: ListResources -> String
showsPrec :: Int -> ListResources -> ShowS
$cshowsPrec :: Int -> ListResources -> ShowS
Prelude.Show, forall x. Rep ListResources x -> ListResources
forall x. ListResources -> Rep ListResources x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListResources x -> ListResources
$cfrom :: forall x. ListResources -> Rep ListResources x
Prelude.Generic)

-- |
-- Create a value of 'ListResources' 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', 'listResources_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', 'listResources_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.
--
-- 'principal', 'listResources_principal' - Specifies that you want to list only the resource shares that are
-- associated with the specified principal.
--
-- 'resourceArns', 'listResources_resourceArns' - Specifies that you want to list only the resource shares that include
-- resources with the specified
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>.
--
-- 'resourceRegionScope', 'listResources_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@.
--
-- 'resourceShareArns', 'listResources_resourceShareArns' - Specifies that you want to list only resources in the resource shares
-- identified by the specified
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>.
--
-- 'resourceType', 'listResources_resourceType' - Specifies that you want to list only the resource shares that include
-- resources of the specified resource type.
--
-- For valid values, query the ListResourceTypes operation.
--
-- 'resourceOwner', 'listResources_resourceOwner' - Specifies that you want to list only the resource shares that match the
-- following:
--
-- -   __@SELF@__ – resources that your account shares with other accounts
--
-- -   __@OTHER-ACCOUNTS@__ – resources that other accounts share with your
--     account
newListResources ::
  -- | 'resourceOwner'
  ResourceOwner ->
  ListResources
newListResources :: ResourceOwner -> ListResources
newListResources ResourceOwner
pResourceOwner_ =
  ListResources'
    { $sel:maxResults:ListResources' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListResources' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:principal:ListResources' :: Maybe Text
principal = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceArns:ListResources' :: Maybe [Text]
resourceArns = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceRegionScope:ListResources' :: Maybe ResourceRegionScopeFilter
resourceRegionScope = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceShareArns:ListResources' :: Maybe [Text]
resourceShareArns = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceType:ListResources' :: Maybe Text
resourceType = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceOwner:ListResources' :: 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.
listResources_maxResults :: Lens.Lens' ListResources (Prelude.Maybe Prelude.Natural)
listResources_maxResults :: Lens' ListResources (Maybe Natural)
listResources_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResources' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListResources' :: ListResources -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListResources
s@ListResources' {} Maybe Natural
a -> ListResources
s {$sel:maxResults:ListResources' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListResources)

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

-- | Specifies that you want to list only the resource shares that are
-- associated with the specified principal.
listResources_principal :: Lens.Lens' ListResources (Prelude.Maybe Prelude.Text)
listResources_principal :: Lens' ListResources (Maybe Text)
listResources_principal = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResources' {Maybe Text
principal :: Maybe Text
$sel:principal:ListResources' :: ListResources -> Maybe Text
principal} -> Maybe Text
principal) (\s :: ListResources
s@ListResources' {} Maybe Text
a -> ListResources
s {$sel:principal:ListResources' :: Maybe Text
principal = Maybe Text
a} :: ListResources)

-- | Specifies that you want to list only the resource shares that include
-- resources with the specified
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>.
listResources_resourceArns :: Lens.Lens' ListResources (Prelude.Maybe [Prelude.Text])
listResources_resourceArns :: Lens' ListResources (Maybe [Text])
listResources_resourceArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResources' {Maybe [Text]
resourceArns :: Maybe [Text]
$sel:resourceArns:ListResources' :: ListResources -> Maybe [Text]
resourceArns} -> Maybe [Text]
resourceArns) (\s :: ListResources
s@ListResources' {} Maybe [Text]
a -> ListResources
s {$sel:resourceArns:ListResources' :: Maybe [Text]
resourceArns = Maybe [Text]
a} :: ListResources) 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 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@.
listResources_resourceRegionScope :: Lens.Lens' ListResources (Prelude.Maybe ResourceRegionScopeFilter)
listResources_resourceRegionScope :: Lens' ListResources (Maybe ResourceRegionScopeFilter)
listResources_resourceRegionScope = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResources' {Maybe ResourceRegionScopeFilter
resourceRegionScope :: Maybe ResourceRegionScopeFilter
$sel:resourceRegionScope:ListResources' :: ListResources -> Maybe ResourceRegionScopeFilter
resourceRegionScope} -> Maybe ResourceRegionScopeFilter
resourceRegionScope) (\s :: ListResources
s@ListResources' {} Maybe ResourceRegionScopeFilter
a -> ListResources
s {$sel:resourceRegionScope:ListResources' :: Maybe ResourceRegionScopeFilter
resourceRegionScope = Maybe ResourceRegionScopeFilter
a} :: ListResources)

-- | Specifies that you want to list only resources in the resource shares
-- identified by the specified
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>.
listResources_resourceShareArns :: Lens.Lens' ListResources (Prelude.Maybe [Prelude.Text])
listResources_resourceShareArns :: Lens' ListResources (Maybe [Text])
listResources_resourceShareArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResources' {Maybe [Text]
resourceShareArns :: Maybe [Text]
$sel:resourceShareArns:ListResources' :: ListResources -> Maybe [Text]
resourceShareArns} -> Maybe [Text]
resourceShareArns) (\s :: ListResources
s@ListResources' {} Maybe [Text]
a -> ListResources
s {$sel:resourceShareArns:ListResources' :: Maybe [Text]
resourceShareArns = Maybe [Text]
a} :: ListResources) 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 only the resource shares that include
-- resources of the specified resource type.
--
-- For valid values, query the ListResourceTypes operation.
listResources_resourceType :: Lens.Lens' ListResources (Prelude.Maybe Prelude.Text)
listResources_resourceType :: Lens' ListResources (Maybe Text)
listResources_resourceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResources' {Maybe Text
resourceType :: Maybe Text
$sel:resourceType:ListResources' :: ListResources -> Maybe Text
resourceType} -> Maybe Text
resourceType) (\s :: ListResources
s@ListResources' {} Maybe Text
a -> ListResources
s {$sel:resourceType:ListResources' :: Maybe Text
resourceType = Maybe Text
a} :: ListResources)

-- | Specifies that you want to list only the resource shares that match the
-- following:
--
-- -   __@SELF@__ – resources that your account shares with other accounts
--
-- -   __@OTHER-ACCOUNTS@__ – resources that other accounts share with your
--     account
listResources_resourceOwner :: Lens.Lens' ListResources ResourceOwner
listResources_resourceOwner :: Lens' ListResources ResourceOwner
listResources_resourceOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResources' {ResourceOwner
resourceOwner :: ResourceOwner
$sel:resourceOwner:ListResources' :: ListResources -> ResourceOwner
resourceOwner} -> ResourceOwner
resourceOwner) (\s :: ListResources
s@ListResources' {} ResourceOwner
a -> ListResources
s {$sel:resourceOwner:ListResources' :: ResourceOwner
resourceOwner = ResourceOwner
a} :: ListResources)

instance Core.AWSPager ListResources where
  page :: ListResources -> AWSResponse ListResources -> Maybe ListResources
page ListResources
rq AWSResponse ListResources
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListResources
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListResourcesResponse (Maybe Text)
listResourcesResponse_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 ListResources
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListResourcesResponse (Maybe [Resource])
listResourcesResponse_resources
            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.$ ListResources
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListResources (Maybe Text)
listResources_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListResources
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListResourcesResponse (Maybe Text)
listResourcesResponse_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 ListResources where
  type
    AWSResponse ListResources =
      ListResourcesResponse
  request :: (Service -> Service) -> ListResources -> Request ListResources
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 ListResources
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListResources)))
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 -> ListResourcesResponse
ListResourcesResponse'
            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 ListResources where
  hashWithSalt :: Int -> ListResources -> Int
hashWithSalt Int
_salt ListResources' {Maybe Natural
Maybe [Text]
Maybe Text
Maybe ResourceRegionScopeFilter
ResourceOwner
resourceOwner :: ResourceOwner
resourceType :: Maybe Text
resourceShareArns :: Maybe [Text]
resourceRegionScope :: Maybe ResourceRegionScopeFilter
resourceArns :: Maybe [Text]
principal :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceOwner:ListResources' :: ListResources -> ResourceOwner
$sel:resourceType:ListResources' :: ListResources -> Maybe Text
$sel:resourceShareArns:ListResources' :: ListResources -> Maybe [Text]
$sel:resourceRegionScope:ListResources' :: ListResources -> Maybe ResourceRegionScopeFilter
$sel:resourceArns:ListResources' :: ListResources -> Maybe [Text]
$sel:principal:ListResources' :: ListResources -> Maybe Text
$sel:nextToken:ListResources' :: ListResources -> Maybe Text
$sel:maxResults:ListResources' :: ListResources -> 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
principal
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
resourceArns
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ResourceRegionScopeFilter
resourceRegionScope
      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 ListResources where
  rnf :: ListResources -> ()
rnf ListResources' {Maybe Natural
Maybe [Text]
Maybe Text
Maybe ResourceRegionScopeFilter
ResourceOwner
resourceOwner :: ResourceOwner
resourceType :: Maybe Text
resourceShareArns :: Maybe [Text]
resourceRegionScope :: Maybe ResourceRegionScopeFilter
resourceArns :: Maybe [Text]
principal :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceOwner:ListResources' :: ListResources -> ResourceOwner
$sel:resourceType:ListResources' :: ListResources -> Maybe Text
$sel:resourceShareArns:ListResources' :: ListResources -> Maybe [Text]
$sel:resourceRegionScope:ListResources' :: ListResources -> Maybe ResourceRegionScopeFilter
$sel:resourceArns:ListResources' :: ListResources -> Maybe [Text]
$sel:principal:ListResources' :: ListResources -> Maybe Text
$sel:nextToken:ListResources' :: ListResources -> Maybe Text
$sel:maxResults:ListResources' :: ListResources -> 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
principal
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
resourceArns
      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 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 ListResources where
  toHeaders :: ListResources -> 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 ListResources where
  toJSON :: ListResources -> Value
toJSON ListResources' {Maybe Natural
Maybe [Text]
Maybe Text
Maybe ResourceRegionScopeFilter
ResourceOwner
resourceOwner :: ResourceOwner
resourceType :: Maybe Text
resourceShareArns :: Maybe [Text]
resourceRegionScope :: Maybe ResourceRegionScopeFilter
resourceArns :: Maybe [Text]
principal :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceOwner:ListResources' :: ListResources -> ResourceOwner
$sel:resourceType:ListResources' :: ListResources -> Maybe Text
$sel:resourceShareArns:ListResources' :: ListResources -> Maybe [Text]
$sel:resourceRegionScope:ListResources' :: ListResources -> Maybe ResourceRegionScopeFilter
$sel:resourceArns:ListResources' :: ListResources -> Maybe [Text]
$sel:principal:ListResources' :: ListResources -> Maybe Text
$sel:nextToken:ListResources' :: ListResources -> Maybe Text
$sel:maxResults:ListResources' :: ListResources -> 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
"principal" 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
principal,
            (Key
"resourceArns" 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]
resourceArns,
            (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,
            (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 ListResources where
  toPath :: ListResources -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/listresources"

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

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

-- |
-- Create a value of 'ListResourcesResponse' 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', 'listResourcesResponse_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', 'listResourcesResponse_resources' - An array of objects that contain information about the resources.
--
-- 'httpStatus', 'listResourcesResponse_httpStatus' - The response's http status code.
newListResourcesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListResourcesResponse
newListResourcesResponse :: Int -> ListResourcesResponse
newListResourcesResponse Int
pHttpStatus_ =
  ListResourcesResponse'
    { $sel:nextToken:ListResourcesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:resources:ListResourcesResponse' :: Maybe [Resource]
resources = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListResourcesResponse' :: 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.
listResourcesResponse_nextToken :: Lens.Lens' ListResourcesResponse (Prelude.Maybe Prelude.Text)
listResourcesResponse_nextToken :: Lens' ListResourcesResponse (Maybe Text)
listResourcesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourcesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListResourcesResponse' :: ListResourcesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListResourcesResponse
s@ListResourcesResponse' {} Maybe Text
a -> ListResourcesResponse
s {$sel:nextToken:ListResourcesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListResourcesResponse)

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

instance Prelude.NFData ListResourcesResponse where
  rnf :: ListResourcesResponse -> ()
rnf ListResourcesResponse' {Int
Maybe [Resource]
Maybe Text
httpStatus :: Int
resources :: Maybe [Resource]
nextToken :: Maybe Text
$sel:httpStatus:ListResourcesResponse' :: ListResourcesResponse -> Int
$sel:resources:ListResourcesResponse' :: ListResourcesResponse -> Maybe [Resource]
$sel:nextToken:ListResourcesResponse' :: ListResourcesResponse -> 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