{-# 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.CloudControl.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)
--
-- Returns information about the specified resources. For more information,
-- see
-- <https://docs.aws.amazon.com/cloudcontrolapi/latest/userguide/resource-operations-list.html Discovering resources>
-- in the /Amazon Web Services Cloud Control API User Guide/.
--
-- You can use this action to return information about existing resources
-- in your account and Amazon Web Services Region, whether those resources
-- were provisioned using Cloud Control API.
--
-- This operation returns paginated results.
module Amazonka.CloudControl.ListResources
  ( -- * Creating a Request
    ListResources (..),
    newListResources,

    -- * Request Lenses
    listResources_maxResults,
    listResources_nextToken,
    listResources_resourceModel,
    listResources_roleArn,
    listResources_typeVersionId,
    listResources_typeName,

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

    -- * Response Lenses
    listResourcesResponse_nextToken,
    listResourcesResponse_resourceDescriptions,
    listResourcesResponse_typeName,
    listResourcesResponse_httpStatus,
  )
where

import Amazonka.CloudControl.Types
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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newListResources' smart constructor.
data ListResources = ListResources'
  { -- | Reserved.
    ListResources -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | If the previous paginated request didn\'t return all of the remaining
    -- results, the response object\'s @NextToken@ parameter value is set to a
    -- token. To retrieve the next set of results, call this action again and
    -- assign that token to the request object\'s @NextToken@ parameter. If
    -- there are no remaining results, the previous response object\'s
    -- @NextToken@ parameter is set to @null@.
    ListResources -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The resource model to use to select the resources to return.
    ListResources -> Maybe (Sensitive Text)
resourceModel :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The Amazon Resource Name (ARN) of the Identity and Access Management
    -- (IAM) role for Cloud Control API to use when performing this resource
    -- operation. The role specified must have the permissions required for
    -- this operation. The necessary permissions for each event handler are
    -- defined in the
    -- @ @<https://docs.aws.amazon.com/cloudformation-cli/latest/userguide/resource-type-schema.html#schema-properties-handlers handlers>@ @
    -- section of the
    -- <https://docs.aws.amazon.com/cloudformation-cli/latest/userguide/resource-type-schema.html resource type definition schema>.
    --
    -- If you do not specify a role, Cloud Control API uses a temporary session
    -- created using your Amazon Web Services user credentials.
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/cloudcontrolapi/latest/userguide/resource-operations.html#resource-operations-permissions Specifying credentials>
    -- in the /Amazon Web Services Cloud Control API User Guide/.
    ListResources -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    -- | For private resource types, the type version to use in this resource
    -- operation. If you do not specify a resource version, CloudFormation uses
    -- the default version.
    ListResources -> Maybe Text
typeVersionId :: Prelude.Maybe Prelude.Text,
    -- | The name of the resource type.
    ListResources -> Text
typeName :: Prelude.Text
  }
  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, 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' - Reserved.
--
-- 'nextToken', 'listResources_nextToken' - If the previous paginated request didn\'t return all of the remaining
-- results, the response object\'s @NextToken@ parameter value is set to a
-- token. To retrieve the next set of results, call this action again and
-- assign that token to the request object\'s @NextToken@ parameter. If
-- there are no remaining results, the previous response object\'s
-- @NextToken@ parameter is set to @null@.
--
-- 'resourceModel', 'listResources_resourceModel' - The resource model to use to select the resources to return.
--
-- 'roleArn', 'listResources_roleArn' - The Amazon Resource Name (ARN) of the Identity and Access Management
-- (IAM) role for Cloud Control API to use when performing this resource
-- operation. The role specified must have the permissions required for
-- this operation. The necessary permissions for each event handler are
-- defined in the
-- @ @<https://docs.aws.amazon.com/cloudformation-cli/latest/userguide/resource-type-schema.html#schema-properties-handlers handlers>@ @
-- section of the
-- <https://docs.aws.amazon.com/cloudformation-cli/latest/userguide/resource-type-schema.html resource type definition schema>.
--
-- If you do not specify a role, Cloud Control API uses a temporary session
-- created using your Amazon Web Services user credentials.
--
-- For more information, see
-- <https://docs.aws.amazon.com/cloudcontrolapi/latest/userguide/resource-operations.html#resource-operations-permissions Specifying credentials>
-- in the /Amazon Web Services Cloud Control API User Guide/.
--
-- 'typeVersionId', 'listResources_typeVersionId' - For private resource types, the type version to use in this resource
-- operation. If you do not specify a resource version, CloudFormation uses
-- the default version.
--
-- 'typeName', 'listResources_typeName' - The name of the resource type.
newListResources ::
  -- | 'typeName'
  Prelude.Text ->
  ListResources
newListResources :: Text -> ListResources
newListResources Text
pTypeName_ =
  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:resourceModel:ListResources' :: Maybe (Sensitive Text)
resourceModel = forall a. Maybe a
Prelude.Nothing,
      $sel:roleArn:ListResources' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:typeVersionId:ListResources' :: Maybe Text
typeVersionId = forall a. Maybe a
Prelude.Nothing,
      $sel:typeName:ListResources' :: Text
typeName = Text
pTypeName_
    }

-- | Reserved.
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)

-- | If the previous paginated request didn\'t return all of the remaining
-- results, the response object\'s @NextToken@ parameter value is set to a
-- token. To retrieve the next set of results, call this action again and
-- assign that token to the request object\'s @NextToken@ parameter. If
-- there are no remaining results, the previous response object\'s
-- @NextToken@ parameter is set to @null@.
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)

-- | The resource model to use to select the resources to return.
listResources_resourceModel :: Lens.Lens' ListResources (Prelude.Maybe Prelude.Text)
listResources_resourceModel :: Lens' ListResources (Maybe Text)
listResources_resourceModel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResources' {Maybe (Sensitive Text)
resourceModel :: Maybe (Sensitive Text)
$sel:resourceModel:ListResources' :: ListResources -> Maybe (Sensitive Text)
resourceModel} -> Maybe (Sensitive Text)
resourceModel) (\s :: ListResources
s@ListResources' {} Maybe (Sensitive Text)
a -> ListResources
s {$sel:resourceModel:ListResources' :: Maybe (Sensitive Text)
resourceModel = Maybe (Sensitive 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 a. Iso' (Sensitive a) a
Data._Sensitive

-- | The Amazon Resource Name (ARN) of the Identity and Access Management
-- (IAM) role for Cloud Control API to use when performing this resource
-- operation. The role specified must have the permissions required for
-- this operation. The necessary permissions for each event handler are
-- defined in the
-- @ @<https://docs.aws.amazon.com/cloudformation-cli/latest/userguide/resource-type-schema.html#schema-properties-handlers handlers>@ @
-- section of the
-- <https://docs.aws.amazon.com/cloudformation-cli/latest/userguide/resource-type-schema.html resource type definition schema>.
--
-- If you do not specify a role, Cloud Control API uses a temporary session
-- created using your Amazon Web Services user credentials.
--
-- For more information, see
-- <https://docs.aws.amazon.com/cloudcontrolapi/latest/userguide/resource-operations.html#resource-operations-permissions Specifying credentials>
-- in the /Amazon Web Services Cloud Control API User Guide/.
listResources_roleArn :: Lens.Lens' ListResources (Prelude.Maybe Prelude.Text)
listResources_roleArn :: Lens' ListResources (Maybe Text)
listResources_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResources' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:ListResources' :: ListResources -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: ListResources
s@ListResources' {} Maybe Text
a -> ListResources
s {$sel:roleArn:ListResources' :: Maybe Text
roleArn = Maybe Text
a} :: ListResources)

-- | For private resource types, the type version to use in this resource
-- operation. If you do not specify a resource version, CloudFormation uses
-- the default version.
listResources_typeVersionId :: Lens.Lens' ListResources (Prelude.Maybe Prelude.Text)
listResources_typeVersionId :: Lens' ListResources (Maybe Text)
listResources_typeVersionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResources' {Maybe Text
typeVersionId :: Maybe Text
$sel:typeVersionId:ListResources' :: ListResources -> Maybe Text
typeVersionId} -> Maybe Text
typeVersionId) (\s :: ListResources
s@ListResources' {} Maybe Text
a -> ListResources
s {$sel:typeVersionId:ListResources' :: Maybe Text
typeVersionId = Maybe Text
a} :: ListResources)

-- | The name of the resource type.
listResources_typeName :: Lens.Lens' ListResources Prelude.Text
listResources_typeName :: Lens' ListResources Text
listResources_typeName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResources' {Text
typeName :: Text
$sel:typeName:ListResources' :: ListResources -> Text
typeName} -> Text
typeName) (\s :: ListResources
s@ListResources' {} Text
a -> ListResources
s {$sel:typeName:ListResources' :: Text
typeName = Text
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 [ResourceDescription])
listResourcesResponse_resourceDescriptions
            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 [ResourceDescription]
-> Maybe Text
-> 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
"ResourceDescriptions"
                            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
"TypeName")
            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 (Sensitive Text)
Text
typeName :: Text
typeVersionId :: Maybe Text
roleArn :: Maybe Text
resourceModel :: Maybe (Sensitive Text)
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:typeName:ListResources' :: ListResources -> Text
$sel:typeVersionId:ListResources' :: ListResources -> Maybe Text
$sel:roleArn:ListResources' :: ListResources -> Maybe Text
$sel:resourceModel:ListResources' :: ListResources -> Maybe (Sensitive 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 (Sensitive Text)
resourceModel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
roleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
typeVersionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
typeName

instance Prelude.NFData ListResources where
  rnf :: ListResources -> ()
rnf ListResources' {Maybe Natural
Maybe Text
Maybe (Sensitive Text)
Text
typeName :: Text
typeVersionId :: Maybe Text
roleArn :: Maybe Text
resourceModel :: Maybe (Sensitive Text)
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:typeName:ListResources' :: ListResources -> Text
$sel:typeVersionId:ListResources' :: ListResources -> Maybe Text
$sel:roleArn:ListResources' :: ListResources -> Maybe Text
$sel:resourceModel:ListResources' :: ListResources -> Maybe (Sensitive 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 (Sensitive Text)
resourceModel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
typeVersionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
typeName

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
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"CloudApiService.ListResources" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON ListResources where
  toJSON :: ListResources -> Value
toJSON ListResources' {Maybe Natural
Maybe Text
Maybe (Sensitive Text)
Text
typeName :: Text
typeVersionId :: Maybe Text
roleArn :: Maybe Text
resourceModel :: Maybe (Sensitive Text)
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:typeName:ListResources' :: ListResources -> Text
$sel:typeVersionId:ListResources' :: ListResources -> Maybe Text
$sel:roleArn:ListResources' :: ListResources -> Maybe Text
$sel:resourceModel:ListResources' :: ListResources -> Maybe (Sensitive 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
"ResourceModel" 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 (Sensitive Text)
resourceModel,
            (Key
"RoleArn" 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
roleArn,
            (Key
"TypeVersionId" 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
typeVersionId,
            forall a. a -> Maybe a
Prelude.Just (Key
"TypeName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
typeName)
          ]
      )

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

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 the request doesn\'t return all of the remaining results, @NextToken@
    -- is set to a token. To retrieve the next set of results, call
    -- @ListResources@ again and assign that token to the request object\'s
    -- @NextToken@ parameter. If the request returns all results, @NextToken@
    -- is set to null.
    ListResourcesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Information about the specified resources, including primary identifier
    -- and resource model.
    ListResourcesResponse -> Maybe [ResourceDescription]
resourceDescriptions :: Prelude.Maybe [ResourceDescription],
    -- | The name of the resource type.
    ListResourcesResponse -> Maybe Text
typeName :: Prelude.Maybe Prelude.Text,
    -- | 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, 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 the request doesn\'t return all of the remaining results, @NextToken@
-- is set to a token. To retrieve the next set of results, call
-- @ListResources@ again and assign that token to the request object\'s
-- @NextToken@ parameter. If the request returns all results, @NextToken@
-- is set to null.
--
-- 'resourceDescriptions', 'listResourcesResponse_resourceDescriptions' - Information about the specified resources, including primary identifier
-- and resource model.
--
-- 'typeName', 'listResourcesResponse_typeName' - The name of the resource type.
--
-- '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:resourceDescriptions:ListResourcesResponse' :: Maybe [ResourceDescription]
resourceDescriptions = forall a. Maybe a
Prelude.Nothing,
      $sel:typeName:ListResourcesResponse' :: Maybe Text
typeName = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListResourcesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | If the request doesn\'t return all of the remaining results, @NextToken@
-- is set to a token. To retrieve the next set of results, call
-- @ListResources@ again and assign that token to the request object\'s
-- @NextToken@ parameter. If the request returns all results, @NextToken@
-- is set to null.
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)

-- | Information about the specified resources, including primary identifier
-- and resource model.
listResourcesResponse_resourceDescriptions :: Lens.Lens' ListResourcesResponse (Prelude.Maybe [ResourceDescription])
listResourcesResponse_resourceDescriptions :: Lens' ListResourcesResponse (Maybe [ResourceDescription])
listResourcesResponse_resourceDescriptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourcesResponse' {Maybe [ResourceDescription]
resourceDescriptions :: Maybe [ResourceDescription]
$sel:resourceDescriptions:ListResourcesResponse' :: ListResourcesResponse -> Maybe [ResourceDescription]
resourceDescriptions} -> Maybe [ResourceDescription]
resourceDescriptions) (\s :: ListResourcesResponse
s@ListResourcesResponse' {} Maybe [ResourceDescription]
a -> ListResourcesResponse
s {$sel:resourceDescriptions:ListResourcesResponse' :: Maybe [ResourceDescription]
resourceDescriptions = Maybe [ResourceDescription]
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 name of the resource type.
listResourcesResponse_typeName :: Lens.Lens' ListResourcesResponse (Prelude.Maybe Prelude.Text)
listResourcesResponse_typeName :: Lens' ListResourcesResponse (Maybe Text)
listResourcesResponse_typeName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourcesResponse' {Maybe Text
typeName :: Maybe Text
$sel:typeName:ListResourcesResponse' :: ListResourcesResponse -> Maybe Text
typeName} -> Maybe Text
typeName) (\s :: ListResourcesResponse
s@ListResourcesResponse' {} Maybe Text
a -> ListResourcesResponse
s {$sel:typeName:ListResourcesResponse' :: Maybe Text
typeName = Maybe Text
a} :: ListResourcesResponse)

-- | 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 [ResourceDescription]
Maybe Text
httpStatus :: Int
typeName :: Maybe Text
resourceDescriptions :: Maybe [ResourceDescription]
nextToken :: Maybe Text
$sel:httpStatus:ListResourcesResponse' :: ListResourcesResponse -> Int
$sel:typeName:ListResourcesResponse' :: ListResourcesResponse -> Maybe Text
$sel:resourceDescriptions:ListResourcesResponse' :: ListResourcesResponse -> Maybe [ResourceDescription]
$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 [ResourceDescription]
resourceDescriptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
typeName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus