{-# 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.ListResourceTypes
-- 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 resource types that can be shared by RAM.
module Amazonka.RAM.ListResourceTypes
  ( -- * Creating a Request
    ListResourceTypes (..),
    newListResourceTypes,

    -- * Request Lenses
    listResourceTypes_maxResults,
    listResourceTypes_nextToken,
    listResourceTypes_resourceRegionScope,

    -- * Destructuring the Response
    ListResourceTypesResponse (..),
    newListResourceTypesResponse,

    -- * Response Lenses
    listResourceTypesResponse_nextToken,
    listResourceTypesResponse_resourceTypes,
    listResourceTypesResponse_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:/ 'newListResourceTypes' smart constructor.
data ListResourceTypes = ListResourceTypes'
  { -- | 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.
    ListResourceTypes -> 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.
    ListResourceTypes -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Specifies that you want the results to include only resources that have
    -- the specified scope.
    --
    -- -   @ALL@ – the results include both global and regional resources or
    --     resource types.
    --
    -- -   @GLOBAL@ – the results include only global resources or resource
    --     types.
    --
    -- -   @REGIONAL@ – the results include only regional resources or resource
    --     types.
    --
    -- The default value is @ALL@.
    ListResourceTypes -> Maybe ResourceRegionScopeFilter
resourceRegionScope :: Prelude.Maybe ResourceRegionScopeFilter
  }
  deriving (ListResourceTypes -> ListResourceTypes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListResourceTypes -> ListResourceTypes -> Bool
$c/= :: ListResourceTypes -> ListResourceTypes -> Bool
== :: ListResourceTypes -> ListResourceTypes -> Bool
$c== :: ListResourceTypes -> ListResourceTypes -> Bool
Prelude.Eq, ReadPrec [ListResourceTypes]
ReadPrec ListResourceTypes
Int -> ReadS ListResourceTypes
ReadS [ListResourceTypes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListResourceTypes]
$creadListPrec :: ReadPrec [ListResourceTypes]
readPrec :: ReadPrec ListResourceTypes
$creadPrec :: ReadPrec ListResourceTypes
readList :: ReadS [ListResourceTypes]
$creadList :: ReadS [ListResourceTypes]
readsPrec :: Int -> ReadS ListResourceTypes
$creadsPrec :: Int -> ReadS ListResourceTypes
Prelude.Read, Int -> ListResourceTypes -> ShowS
[ListResourceTypes] -> ShowS
ListResourceTypes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListResourceTypes] -> ShowS
$cshowList :: [ListResourceTypes] -> ShowS
show :: ListResourceTypes -> String
$cshow :: ListResourceTypes -> String
showsPrec :: Int -> ListResourceTypes -> ShowS
$cshowsPrec :: Int -> ListResourceTypes -> ShowS
Prelude.Show, forall x. Rep ListResourceTypes x -> ListResourceTypes
forall x. ListResourceTypes -> Rep ListResourceTypes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListResourceTypes x -> ListResourceTypes
$cfrom :: forall x. ListResourceTypes -> Rep ListResourceTypes x
Prelude.Generic)

-- |
-- Create a value of 'ListResourceTypes' 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', 'listResourceTypes_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', 'listResourceTypes_nextToken' - Specifies that you want to receive the next page of results. Valid only
-- if you received a @NextToken@ response in the previous request. If you
-- did, it indicates that more output is available. Set this parameter to
-- the value provided by the previous call\'s @NextToken@ response to
-- request the next page of results.
--
-- 'resourceRegionScope', 'listResourceTypes_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@.
newListResourceTypes ::
  ListResourceTypes
newListResourceTypes :: ListResourceTypes
newListResourceTypes =
  ListResourceTypes'
    { $sel:maxResults:ListResourceTypes' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListResourceTypes' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceRegionScope:ListResourceTypes' :: Maybe ResourceRegionScopeFilter
resourceRegionScope = 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.
listResourceTypes_maxResults :: Lens.Lens' ListResourceTypes (Prelude.Maybe Prelude.Natural)
listResourceTypes_maxResults :: Lens' ListResourceTypes (Maybe Natural)
listResourceTypes_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceTypes' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListResourceTypes' :: ListResourceTypes -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListResourceTypes
s@ListResourceTypes' {} Maybe Natural
a -> ListResourceTypes
s {$sel:maxResults:ListResourceTypes' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListResourceTypes)

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

-- | 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@.
listResourceTypes_resourceRegionScope :: Lens.Lens' ListResourceTypes (Prelude.Maybe ResourceRegionScopeFilter)
listResourceTypes_resourceRegionScope :: Lens' ListResourceTypes (Maybe ResourceRegionScopeFilter)
listResourceTypes_resourceRegionScope = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceTypes' {Maybe ResourceRegionScopeFilter
resourceRegionScope :: Maybe ResourceRegionScopeFilter
$sel:resourceRegionScope:ListResourceTypes' :: ListResourceTypes -> Maybe ResourceRegionScopeFilter
resourceRegionScope} -> Maybe ResourceRegionScopeFilter
resourceRegionScope) (\s :: ListResourceTypes
s@ListResourceTypes' {} Maybe ResourceRegionScopeFilter
a -> ListResourceTypes
s {$sel:resourceRegionScope:ListResourceTypes' :: Maybe ResourceRegionScopeFilter
resourceRegionScope = Maybe ResourceRegionScopeFilter
a} :: ListResourceTypes)

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

instance Prelude.NFData ListResourceTypes where
  rnf :: ListResourceTypes -> ()
rnf ListResourceTypes' {Maybe Natural
Maybe Text
Maybe ResourceRegionScopeFilter
resourceRegionScope :: Maybe ResourceRegionScopeFilter
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceRegionScope:ListResourceTypes' :: ListResourceTypes -> Maybe ResourceRegionScopeFilter
$sel:nextToken:ListResourceTypes' :: ListResourceTypes -> Maybe Text
$sel:maxResults:ListResourceTypes' :: ListResourceTypes -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ResourceRegionScopeFilter
resourceRegionScope

instance Data.ToHeaders ListResourceTypes where
  toHeaders :: ListResourceTypes -> 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 ListResourceTypes where
  toJSON :: ListResourceTypes -> Value
toJSON ListResourceTypes' {Maybe Natural
Maybe Text
Maybe ResourceRegionScopeFilter
resourceRegionScope :: Maybe ResourceRegionScopeFilter
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceRegionScope:ListResourceTypes' :: ListResourceTypes -> Maybe ResourceRegionScopeFilter
$sel:nextToken:ListResourceTypes' :: ListResourceTypes -> Maybe Text
$sel:maxResults:ListResourceTypes' :: ListResourceTypes -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"maxResults" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
maxResults,
            (Key
"nextToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
nextToken,
            (Key
"resourceRegionScope" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ResourceRegionScopeFilter
resourceRegionScope
          ]
      )

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

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

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

-- |
-- Create a value of 'ListResourceTypesResponse' 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', 'listResourceTypesResponse_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.
--
-- 'resourceTypes', 'listResourceTypesResponse_resourceTypes' - An array of objects that contain information about the resource types
-- that can be shared using RAM.
--
-- 'httpStatus', 'listResourceTypesResponse_httpStatus' - The response's http status code.
newListResourceTypesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListResourceTypesResponse
newListResourceTypesResponse :: Int -> ListResourceTypesResponse
newListResourceTypesResponse Int
pHttpStatus_ =
  ListResourceTypesResponse'
    { $sel:nextToken:ListResourceTypesResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:resourceTypes:ListResourceTypesResponse' :: Maybe [ServiceNameAndResourceType]
resourceTypes = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListResourceTypesResponse' :: 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.
listResourceTypesResponse_nextToken :: Lens.Lens' ListResourceTypesResponse (Prelude.Maybe Prelude.Text)
listResourceTypesResponse_nextToken :: Lens' ListResourceTypesResponse (Maybe Text)
listResourceTypesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceTypesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListResourceTypesResponse' :: ListResourceTypesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListResourceTypesResponse
s@ListResourceTypesResponse' {} Maybe Text
a -> ListResourceTypesResponse
s {$sel:nextToken:ListResourceTypesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListResourceTypesResponse)

-- | An array of objects that contain information about the resource types
-- that can be shared using RAM.
listResourceTypesResponse_resourceTypes :: Lens.Lens' ListResourceTypesResponse (Prelude.Maybe [ServiceNameAndResourceType])
listResourceTypesResponse_resourceTypes :: Lens'
  ListResourceTypesResponse (Maybe [ServiceNameAndResourceType])
listResourceTypesResponse_resourceTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceTypesResponse' {Maybe [ServiceNameAndResourceType]
resourceTypes :: Maybe [ServiceNameAndResourceType]
$sel:resourceTypes:ListResourceTypesResponse' :: ListResourceTypesResponse -> Maybe [ServiceNameAndResourceType]
resourceTypes} -> Maybe [ServiceNameAndResourceType]
resourceTypes) (\s :: ListResourceTypesResponse
s@ListResourceTypesResponse' {} Maybe [ServiceNameAndResourceType]
a -> ListResourceTypesResponse
s {$sel:resourceTypes:ListResourceTypesResponse' :: Maybe [ServiceNameAndResourceType]
resourceTypes = Maybe [ServiceNameAndResourceType]
a} :: ListResourceTypesResponse) 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.
listResourceTypesResponse_httpStatus :: Lens.Lens' ListResourceTypesResponse Prelude.Int
listResourceTypesResponse_httpStatus :: Lens' ListResourceTypesResponse Int
listResourceTypesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceTypesResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListResourceTypesResponse' :: ListResourceTypesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListResourceTypesResponse
s@ListResourceTypesResponse' {} Int
a -> ListResourceTypesResponse
s {$sel:httpStatus:ListResourceTypesResponse' :: Int
httpStatus = Int
a} :: ListResourceTypesResponse)

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