{-# 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.Config.ListResourceEvaluations
-- 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 a list of proactive resource evaluations.
--
-- This operation returns paginated results.
module Amazonka.Config.ListResourceEvaluations
  ( -- * Creating a Request
    ListResourceEvaluations (..),
    newListResourceEvaluations,

    -- * Request Lenses
    listResourceEvaluations_filters,
    listResourceEvaluations_limit,
    listResourceEvaluations_nextToken,

    -- * Destructuring the Response
    ListResourceEvaluationsResponse (..),
    newListResourceEvaluationsResponse,

    -- * Response Lenses
    listResourceEvaluationsResponse_nextToken,
    listResourceEvaluationsResponse_resourceEvaluations,
    listResourceEvaluationsResponse_httpStatus,
  )
where

import Amazonka.Config.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:/ 'newListResourceEvaluations' smart constructor.
data ListResourceEvaluations = ListResourceEvaluations'
  { -- | Returns a @ResourceEvaluationFilters@ object.
    ListResourceEvaluations -> Maybe ResourceEvaluationFilters
filters :: Prelude.Maybe ResourceEvaluationFilters,
    -- | The maximum number of evaluations returned on each page. The default is
    -- 10. You cannot specify a number greater than 100. If you specify 0,
    -- Config uses the default.
    ListResourceEvaluations -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
    -- | The @nextToken@ string returned on a previous page that you use to get
    -- the next page of results in a paginated response.
    ListResourceEvaluations -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListResourceEvaluations -> ListResourceEvaluations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListResourceEvaluations -> ListResourceEvaluations -> Bool
$c/= :: ListResourceEvaluations -> ListResourceEvaluations -> Bool
== :: ListResourceEvaluations -> ListResourceEvaluations -> Bool
$c== :: ListResourceEvaluations -> ListResourceEvaluations -> Bool
Prelude.Eq, ReadPrec [ListResourceEvaluations]
ReadPrec ListResourceEvaluations
Int -> ReadS ListResourceEvaluations
ReadS [ListResourceEvaluations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListResourceEvaluations]
$creadListPrec :: ReadPrec [ListResourceEvaluations]
readPrec :: ReadPrec ListResourceEvaluations
$creadPrec :: ReadPrec ListResourceEvaluations
readList :: ReadS [ListResourceEvaluations]
$creadList :: ReadS [ListResourceEvaluations]
readsPrec :: Int -> ReadS ListResourceEvaluations
$creadsPrec :: Int -> ReadS ListResourceEvaluations
Prelude.Read, Int -> ListResourceEvaluations -> ShowS
[ListResourceEvaluations] -> ShowS
ListResourceEvaluations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListResourceEvaluations] -> ShowS
$cshowList :: [ListResourceEvaluations] -> ShowS
show :: ListResourceEvaluations -> String
$cshow :: ListResourceEvaluations -> String
showsPrec :: Int -> ListResourceEvaluations -> ShowS
$cshowsPrec :: Int -> ListResourceEvaluations -> ShowS
Prelude.Show, forall x. Rep ListResourceEvaluations x -> ListResourceEvaluations
forall x. ListResourceEvaluations -> Rep ListResourceEvaluations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListResourceEvaluations x -> ListResourceEvaluations
$cfrom :: forall x. ListResourceEvaluations -> Rep ListResourceEvaluations x
Prelude.Generic)

-- |
-- Create a value of 'ListResourceEvaluations' 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:
--
-- 'filters', 'listResourceEvaluations_filters' - Returns a @ResourceEvaluationFilters@ object.
--
-- 'limit', 'listResourceEvaluations_limit' - The maximum number of evaluations returned on each page. The default is
-- 10. You cannot specify a number greater than 100. If you specify 0,
-- Config uses the default.
--
-- 'nextToken', 'listResourceEvaluations_nextToken' - The @nextToken@ string returned on a previous page that you use to get
-- the next page of results in a paginated response.
newListResourceEvaluations ::
  ListResourceEvaluations
newListResourceEvaluations :: ListResourceEvaluations
newListResourceEvaluations =
  ListResourceEvaluations'
    { $sel:filters:ListResourceEvaluations' :: Maybe ResourceEvaluationFilters
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:limit:ListResourceEvaluations' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListResourceEvaluations' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | Returns a @ResourceEvaluationFilters@ object.
listResourceEvaluations_filters :: Lens.Lens' ListResourceEvaluations (Prelude.Maybe ResourceEvaluationFilters)
listResourceEvaluations_filters :: Lens' ListResourceEvaluations (Maybe ResourceEvaluationFilters)
listResourceEvaluations_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceEvaluations' {Maybe ResourceEvaluationFilters
filters :: Maybe ResourceEvaluationFilters
$sel:filters:ListResourceEvaluations' :: ListResourceEvaluations -> Maybe ResourceEvaluationFilters
filters} -> Maybe ResourceEvaluationFilters
filters) (\s :: ListResourceEvaluations
s@ListResourceEvaluations' {} Maybe ResourceEvaluationFilters
a -> ListResourceEvaluations
s {$sel:filters:ListResourceEvaluations' :: Maybe ResourceEvaluationFilters
filters = Maybe ResourceEvaluationFilters
a} :: ListResourceEvaluations)

-- | The maximum number of evaluations returned on each page. The default is
-- 10. You cannot specify a number greater than 100. If you specify 0,
-- Config uses the default.
listResourceEvaluations_limit :: Lens.Lens' ListResourceEvaluations (Prelude.Maybe Prelude.Natural)
listResourceEvaluations_limit :: Lens' ListResourceEvaluations (Maybe Natural)
listResourceEvaluations_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceEvaluations' {Maybe Natural
limit :: Maybe Natural
$sel:limit:ListResourceEvaluations' :: ListResourceEvaluations -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: ListResourceEvaluations
s@ListResourceEvaluations' {} Maybe Natural
a -> ListResourceEvaluations
s {$sel:limit:ListResourceEvaluations' :: Maybe Natural
limit = Maybe Natural
a} :: ListResourceEvaluations)

-- | The @nextToken@ string returned on a previous page that you use to get
-- the next page of results in a paginated response.
listResourceEvaluations_nextToken :: Lens.Lens' ListResourceEvaluations (Prelude.Maybe Prelude.Text)
listResourceEvaluations_nextToken :: Lens' ListResourceEvaluations (Maybe Text)
listResourceEvaluations_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceEvaluations' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListResourceEvaluations' :: ListResourceEvaluations -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListResourceEvaluations
s@ListResourceEvaluations' {} Maybe Text
a -> ListResourceEvaluations
s {$sel:nextToken:ListResourceEvaluations' :: Maybe Text
nextToken = Maybe Text
a} :: ListResourceEvaluations)

instance Core.AWSPager ListResourceEvaluations where
  page :: ListResourceEvaluations
-> AWSResponse ListResourceEvaluations
-> Maybe ListResourceEvaluations
page ListResourceEvaluations
rq AWSResponse ListResourceEvaluations
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListResourceEvaluations
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListResourceEvaluationsResponse (Maybe Text)
listResourceEvaluationsResponse_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 ListResourceEvaluations
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListResourceEvaluationsResponse (Maybe [ResourceEvaluation])
listResourceEvaluationsResponse_resourceEvaluations
            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.$ ListResourceEvaluations
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListResourceEvaluations (Maybe Text)
listResourceEvaluations_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListResourceEvaluations
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListResourceEvaluationsResponse (Maybe Text)
listResourceEvaluationsResponse_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 ListResourceEvaluations where
  type
    AWSResponse ListResourceEvaluations =
      ListResourceEvaluationsResponse
  request :: (Service -> Service)
-> ListResourceEvaluations -> Request ListResourceEvaluations
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 ListResourceEvaluations
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListResourceEvaluations)))
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 [ResourceEvaluation]
-> Int
-> ListResourceEvaluationsResponse
ListResourceEvaluationsResponse'
            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
"ResourceEvaluations"
                            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 ListResourceEvaluations where
  hashWithSalt :: Int -> ListResourceEvaluations -> Int
hashWithSalt Int
_salt ListResourceEvaluations' {Maybe Natural
Maybe Text
Maybe ResourceEvaluationFilters
nextToken :: Maybe Text
limit :: Maybe Natural
filters :: Maybe ResourceEvaluationFilters
$sel:nextToken:ListResourceEvaluations' :: ListResourceEvaluations -> Maybe Text
$sel:limit:ListResourceEvaluations' :: ListResourceEvaluations -> Maybe Natural
$sel:filters:ListResourceEvaluations' :: ListResourceEvaluations -> Maybe ResourceEvaluationFilters
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ResourceEvaluationFilters
filters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
limit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData ListResourceEvaluations where
  rnf :: ListResourceEvaluations -> ()
rnf ListResourceEvaluations' {Maybe Natural
Maybe Text
Maybe ResourceEvaluationFilters
nextToken :: Maybe Text
limit :: Maybe Natural
filters :: Maybe ResourceEvaluationFilters
$sel:nextToken:ListResourceEvaluations' :: ListResourceEvaluations -> Maybe Text
$sel:limit:ListResourceEvaluations' :: ListResourceEvaluations -> Maybe Natural
$sel:filters:ListResourceEvaluations' :: ListResourceEvaluations -> Maybe ResourceEvaluationFilters
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ResourceEvaluationFilters
filters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
limit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken

instance Data.ToHeaders ListResourceEvaluations where
  toHeaders :: ListResourceEvaluations -> 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
"StarlingDoveService.ListResourceEvaluations" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON ListResourceEvaluations where
  toJSON :: ListResourceEvaluations -> Value
toJSON ListResourceEvaluations' {Maybe Natural
Maybe Text
Maybe ResourceEvaluationFilters
nextToken :: Maybe Text
limit :: Maybe Natural
filters :: Maybe ResourceEvaluationFilters
$sel:nextToken:ListResourceEvaluations' :: ListResourceEvaluations -> Maybe Text
$sel:limit:ListResourceEvaluations' :: ListResourceEvaluations -> Maybe Natural
$sel:filters:ListResourceEvaluations' :: ListResourceEvaluations -> Maybe ResourceEvaluationFilters
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Filters" 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 ResourceEvaluationFilters
filters,
            (Key
"Limit" 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
limit,
            (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
          ]
      )

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

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

-- | /See:/ 'newListResourceEvaluationsResponse' smart constructor.
data ListResourceEvaluationsResponse = ListResourceEvaluationsResponse'
  { -- | The @nextToken@ string returned on a previous page that you use to get
    -- the next page of results in a paginated response.
    ListResourceEvaluationsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Returns a @ResourceEvaluations@ object.
    ListResourceEvaluationsResponse -> Maybe [ResourceEvaluation]
resourceEvaluations :: Prelude.Maybe [ResourceEvaluation],
    -- | The response's http status code.
    ListResourceEvaluationsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListResourceEvaluationsResponse
-> ListResourceEvaluationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListResourceEvaluationsResponse
-> ListResourceEvaluationsResponse -> Bool
$c/= :: ListResourceEvaluationsResponse
-> ListResourceEvaluationsResponse -> Bool
== :: ListResourceEvaluationsResponse
-> ListResourceEvaluationsResponse -> Bool
$c== :: ListResourceEvaluationsResponse
-> ListResourceEvaluationsResponse -> Bool
Prelude.Eq, ReadPrec [ListResourceEvaluationsResponse]
ReadPrec ListResourceEvaluationsResponse
Int -> ReadS ListResourceEvaluationsResponse
ReadS [ListResourceEvaluationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListResourceEvaluationsResponse]
$creadListPrec :: ReadPrec [ListResourceEvaluationsResponse]
readPrec :: ReadPrec ListResourceEvaluationsResponse
$creadPrec :: ReadPrec ListResourceEvaluationsResponse
readList :: ReadS [ListResourceEvaluationsResponse]
$creadList :: ReadS [ListResourceEvaluationsResponse]
readsPrec :: Int -> ReadS ListResourceEvaluationsResponse
$creadsPrec :: Int -> ReadS ListResourceEvaluationsResponse
Prelude.Read, Int -> ListResourceEvaluationsResponse -> ShowS
[ListResourceEvaluationsResponse] -> ShowS
ListResourceEvaluationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListResourceEvaluationsResponse] -> ShowS
$cshowList :: [ListResourceEvaluationsResponse] -> ShowS
show :: ListResourceEvaluationsResponse -> String
$cshow :: ListResourceEvaluationsResponse -> String
showsPrec :: Int -> ListResourceEvaluationsResponse -> ShowS
$cshowsPrec :: Int -> ListResourceEvaluationsResponse -> ShowS
Prelude.Show, forall x.
Rep ListResourceEvaluationsResponse x
-> ListResourceEvaluationsResponse
forall x.
ListResourceEvaluationsResponse
-> Rep ListResourceEvaluationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListResourceEvaluationsResponse x
-> ListResourceEvaluationsResponse
$cfrom :: forall x.
ListResourceEvaluationsResponse
-> Rep ListResourceEvaluationsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListResourceEvaluationsResponse' 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', 'listResourceEvaluationsResponse_nextToken' - The @nextToken@ string returned on a previous page that you use to get
-- the next page of results in a paginated response.
--
-- 'resourceEvaluations', 'listResourceEvaluationsResponse_resourceEvaluations' - Returns a @ResourceEvaluations@ object.
--
-- 'httpStatus', 'listResourceEvaluationsResponse_httpStatus' - The response's http status code.
newListResourceEvaluationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListResourceEvaluationsResponse
newListResourceEvaluationsResponse :: Int -> ListResourceEvaluationsResponse
newListResourceEvaluationsResponse Int
pHttpStatus_ =
  ListResourceEvaluationsResponse'
    { $sel:nextToken:ListResourceEvaluationsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:resourceEvaluations:ListResourceEvaluationsResponse' :: Maybe [ResourceEvaluation]
resourceEvaluations = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListResourceEvaluationsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The @nextToken@ string returned on a previous page that you use to get
-- the next page of results in a paginated response.
listResourceEvaluationsResponse_nextToken :: Lens.Lens' ListResourceEvaluationsResponse (Prelude.Maybe Prelude.Text)
listResourceEvaluationsResponse_nextToken :: Lens' ListResourceEvaluationsResponse (Maybe Text)
listResourceEvaluationsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceEvaluationsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListResourceEvaluationsResponse' :: ListResourceEvaluationsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListResourceEvaluationsResponse
s@ListResourceEvaluationsResponse' {} Maybe Text
a -> ListResourceEvaluationsResponse
s {$sel:nextToken:ListResourceEvaluationsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListResourceEvaluationsResponse)

-- | Returns a @ResourceEvaluations@ object.
listResourceEvaluationsResponse_resourceEvaluations :: Lens.Lens' ListResourceEvaluationsResponse (Prelude.Maybe [ResourceEvaluation])
listResourceEvaluationsResponse_resourceEvaluations :: Lens' ListResourceEvaluationsResponse (Maybe [ResourceEvaluation])
listResourceEvaluationsResponse_resourceEvaluations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceEvaluationsResponse' {Maybe [ResourceEvaluation]
resourceEvaluations :: Maybe [ResourceEvaluation]
$sel:resourceEvaluations:ListResourceEvaluationsResponse' :: ListResourceEvaluationsResponse -> Maybe [ResourceEvaluation]
resourceEvaluations} -> Maybe [ResourceEvaluation]
resourceEvaluations) (\s :: ListResourceEvaluationsResponse
s@ListResourceEvaluationsResponse' {} Maybe [ResourceEvaluation]
a -> ListResourceEvaluationsResponse
s {$sel:resourceEvaluations:ListResourceEvaluationsResponse' :: Maybe [ResourceEvaluation]
resourceEvaluations = Maybe [ResourceEvaluation]
a} :: ListResourceEvaluationsResponse) 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.
listResourceEvaluationsResponse_httpStatus :: Lens.Lens' ListResourceEvaluationsResponse Prelude.Int
listResourceEvaluationsResponse_httpStatus :: Lens' ListResourceEvaluationsResponse Int
listResourceEvaluationsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceEvaluationsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListResourceEvaluationsResponse' :: ListResourceEvaluationsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListResourceEvaluationsResponse
s@ListResourceEvaluationsResponse' {} Int
a -> ListResourceEvaluationsResponse
s {$sel:httpStatus:ListResourceEvaluationsResponse' :: Int
httpStatus = Int
a} :: ListResourceEvaluationsResponse)

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