{-# 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.ResourceGroups.SearchResources
-- 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 AWS resource identifiers that matches the specified
-- query. The query uses the same format as a resource query in a
-- CreateGroup or UpdateGroupQuery operation.
--
-- __Minimum permissions__
--
-- To run this command, you must have the following permissions:
--
-- -   @resource-groups:SearchResources@
--
-- -   @cloudformation:DescribeStacks@
--
-- -   @cloudformation:ListStackResources@
--
-- -   @tag:GetResources@
--
-- This operation returns paginated results.
module Amazonka.ResourceGroups.SearchResources
  ( -- * Creating a Request
    SearchResources (..),
    newSearchResources,

    -- * Request Lenses
    searchResources_maxResults,
    searchResources_nextToken,
    searchResources_resourceQuery,

    -- * Destructuring the Response
    SearchResourcesResponse (..),
    newSearchResourcesResponse,

    -- * Response Lenses
    searchResourcesResponse_nextToken,
    searchResourcesResponse_queryErrors,
    searchResourcesResponse_resourceIdentifiers,
    searchResourcesResponse_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 qualified Amazonka.Request as Request
import Amazonka.ResourceGroups.Types
import qualified Amazonka.Response as Response

-- | /See:/ 'newSearchResources' smart constructor.
data SearchResources = SearchResources'
  { -- | 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
    -- maximum you specify, the @NextToken@ response element is present and has
    -- a value (is not null). Include that 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.
    SearchResources -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The parameter for receiving additional results if you receive a
    -- @NextToken@ response in a previous request. A @NextToken@ response
    -- indicates that more output is available. Set this parameter to the value
    -- provided by a previous call\'s @NextToken@ response to indicate where
    -- the output should continue from.
    SearchResources -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The search query, using the same formats that are supported for resource
    -- group definition. For more information, see CreateGroup.
    SearchResources -> ResourceQuery
resourceQuery :: ResourceQuery
  }
  deriving (SearchResources -> SearchResources -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchResources -> SearchResources -> Bool
$c/= :: SearchResources -> SearchResources -> Bool
== :: SearchResources -> SearchResources -> Bool
$c== :: SearchResources -> SearchResources -> Bool
Prelude.Eq, ReadPrec [SearchResources]
ReadPrec SearchResources
Int -> ReadS SearchResources
ReadS [SearchResources]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SearchResources]
$creadListPrec :: ReadPrec [SearchResources]
readPrec :: ReadPrec SearchResources
$creadPrec :: ReadPrec SearchResources
readList :: ReadS [SearchResources]
$creadList :: ReadS [SearchResources]
readsPrec :: Int -> ReadS SearchResources
$creadsPrec :: Int -> ReadS SearchResources
Prelude.Read, Int -> SearchResources -> ShowS
[SearchResources] -> ShowS
SearchResources -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchResources] -> ShowS
$cshowList :: [SearchResources] -> ShowS
show :: SearchResources -> String
$cshow :: SearchResources -> String
showsPrec :: Int -> SearchResources -> ShowS
$cshowsPrec :: Int -> SearchResources -> ShowS
Prelude.Show, forall x. Rep SearchResources x -> SearchResources
forall x. SearchResources -> Rep SearchResources x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchResources x -> SearchResources
$cfrom :: forall x. SearchResources -> Rep SearchResources x
Prelude.Generic)

-- |
-- Create a value of 'SearchResources' 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', 'searchResources_maxResults' - 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
-- maximum you specify, the @NextToken@ response element is present and has
-- a value (is not null). Include that 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', 'searchResources_nextToken' - The parameter for receiving additional results if you receive a
-- @NextToken@ response in a previous request. A @NextToken@ response
-- indicates that more output is available. Set this parameter to the value
-- provided by a previous call\'s @NextToken@ response to indicate where
-- the output should continue from.
--
-- 'resourceQuery', 'searchResources_resourceQuery' - The search query, using the same formats that are supported for resource
-- group definition. For more information, see CreateGroup.
newSearchResources ::
  -- | 'resourceQuery'
  ResourceQuery ->
  SearchResources
newSearchResources :: ResourceQuery -> SearchResources
newSearchResources ResourceQuery
pResourceQuery_ =
  SearchResources'
    { $sel:maxResults:SearchResources' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:SearchResources' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceQuery:SearchResources' :: ResourceQuery
resourceQuery = ResourceQuery
pResourceQuery_
    }

-- | 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
-- maximum you specify, the @NextToken@ response element is present and has
-- a value (is not null). Include that 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.
searchResources_maxResults :: Lens.Lens' SearchResources (Prelude.Maybe Prelude.Natural)
searchResources_maxResults :: Lens' SearchResources (Maybe Natural)
searchResources_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchResources' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:SearchResources' :: SearchResources -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: SearchResources
s@SearchResources' {} Maybe Natural
a -> SearchResources
s {$sel:maxResults:SearchResources' :: Maybe Natural
maxResults = Maybe Natural
a} :: SearchResources)

-- | The parameter for receiving additional results if you receive a
-- @NextToken@ response in a previous request. A @NextToken@ response
-- indicates that more output is available. Set this parameter to the value
-- provided by a previous call\'s @NextToken@ response to indicate where
-- the output should continue from.
searchResources_nextToken :: Lens.Lens' SearchResources (Prelude.Maybe Prelude.Text)
searchResources_nextToken :: Lens' SearchResources (Maybe Text)
searchResources_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchResources' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:SearchResources' :: SearchResources -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: SearchResources
s@SearchResources' {} Maybe Text
a -> SearchResources
s {$sel:nextToken:SearchResources' :: Maybe Text
nextToken = Maybe Text
a} :: SearchResources)

-- | The search query, using the same formats that are supported for resource
-- group definition. For more information, see CreateGroup.
searchResources_resourceQuery :: Lens.Lens' SearchResources ResourceQuery
searchResources_resourceQuery :: Lens' SearchResources ResourceQuery
searchResources_resourceQuery = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchResources' {ResourceQuery
resourceQuery :: ResourceQuery
$sel:resourceQuery:SearchResources' :: SearchResources -> ResourceQuery
resourceQuery} -> ResourceQuery
resourceQuery) (\s :: SearchResources
s@SearchResources' {} ResourceQuery
a -> SearchResources
s {$sel:resourceQuery:SearchResources' :: ResourceQuery
resourceQuery = ResourceQuery
a} :: SearchResources)

instance Core.AWSPager SearchResources where
  page :: SearchResources
-> AWSResponse SearchResources -> Maybe SearchResources
page SearchResources
rq AWSResponse SearchResources
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse SearchResources
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' SearchResourcesResponse (Maybe Text)
searchResourcesResponse_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 SearchResources
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' SearchResourcesResponse (Maybe [ResourceIdentifier])
searchResourcesResponse_resourceIdentifiers
            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.$ SearchResources
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' SearchResources (Maybe Text)
searchResources_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse SearchResources
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' SearchResourcesResponse (Maybe Text)
searchResourcesResponse_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 SearchResources where
  type
    AWSResponse SearchResources =
      SearchResourcesResponse
  request :: (Service -> Service) -> SearchResources -> Request SearchResources
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 SearchResources
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse SearchResources)))
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 [QueryError]
-> Maybe [ResourceIdentifier]
-> Int
-> SearchResourcesResponse
SearchResourcesResponse'
            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
"QueryErrors" 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
"ResourceIdentifiers"
                            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 SearchResources where
  hashWithSalt :: Int -> SearchResources -> Int
hashWithSalt Int
_salt SearchResources' {Maybe Natural
Maybe Text
ResourceQuery
resourceQuery :: ResourceQuery
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceQuery:SearchResources' :: SearchResources -> ResourceQuery
$sel:nextToken:SearchResources' :: SearchResources -> Maybe Text
$sel:maxResults:SearchResources' :: SearchResources -> 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` ResourceQuery
resourceQuery

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

instance Data.ToHeaders SearchResources where
  toHeaders :: SearchResources -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON SearchResources where
  toJSON :: SearchResources -> Value
toJSON SearchResources' {Maybe Natural
Maybe Text
ResourceQuery
resourceQuery :: ResourceQuery
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceQuery:SearchResources' :: SearchResources -> ResourceQuery
$sel:nextToken:SearchResources' :: SearchResources -> Maybe Text
$sel:maxResults:SearchResources' :: SearchResources -> 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,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ResourceQuery" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ResourceQuery
resourceQuery)
          ]
      )

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

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

-- | /See:/ 'newSearchResourcesResponse' smart constructor.
data SearchResourcesResponse = SearchResourcesResponse'
  { -- | If present, 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@.
    SearchResourcesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A list of @QueryError@ objects. Each error is an object that contains
    -- @ErrorCode@ and @Message@ structures. Possible values for @ErrorCode@
    -- are @CLOUDFORMATION_STACK_INACTIVE@ and
    -- @CLOUDFORMATION_STACK_NOT_EXISTING@.
    SearchResourcesResponse -> Maybe [QueryError]
queryErrors :: Prelude.Maybe [QueryError],
    -- | The ARNs and resource types of resources that are members of the group
    -- that you specified.
    SearchResourcesResponse -> Maybe [ResourceIdentifier]
resourceIdentifiers :: Prelude.Maybe [ResourceIdentifier],
    -- | The response's http status code.
    SearchResourcesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (SearchResourcesResponse -> SearchResourcesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchResourcesResponse -> SearchResourcesResponse -> Bool
$c/= :: SearchResourcesResponse -> SearchResourcesResponse -> Bool
== :: SearchResourcesResponse -> SearchResourcesResponse -> Bool
$c== :: SearchResourcesResponse -> SearchResourcesResponse -> Bool
Prelude.Eq, ReadPrec [SearchResourcesResponse]
ReadPrec SearchResourcesResponse
Int -> ReadS SearchResourcesResponse
ReadS [SearchResourcesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SearchResourcesResponse]
$creadListPrec :: ReadPrec [SearchResourcesResponse]
readPrec :: ReadPrec SearchResourcesResponse
$creadPrec :: ReadPrec SearchResourcesResponse
readList :: ReadS [SearchResourcesResponse]
$creadList :: ReadS [SearchResourcesResponse]
readsPrec :: Int -> ReadS SearchResourcesResponse
$creadsPrec :: Int -> ReadS SearchResourcesResponse
Prelude.Read, Int -> SearchResourcesResponse -> ShowS
[SearchResourcesResponse] -> ShowS
SearchResourcesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchResourcesResponse] -> ShowS
$cshowList :: [SearchResourcesResponse] -> ShowS
show :: SearchResourcesResponse -> String
$cshow :: SearchResourcesResponse -> String
showsPrec :: Int -> SearchResourcesResponse -> ShowS
$cshowsPrec :: Int -> SearchResourcesResponse -> ShowS
Prelude.Show, forall x. Rep SearchResourcesResponse x -> SearchResourcesResponse
forall x. SearchResourcesResponse -> Rep SearchResourcesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchResourcesResponse x -> SearchResourcesResponse
$cfrom :: forall x. SearchResourcesResponse -> Rep SearchResourcesResponse x
Prelude.Generic)

-- |
-- Create a value of 'SearchResourcesResponse' 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', 'searchResourcesResponse_nextToken' - If present, 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@.
--
-- 'queryErrors', 'searchResourcesResponse_queryErrors' - A list of @QueryError@ objects. Each error is an object that contains
-- @ErrorCode@ and @Message@ structures. Possible values for @ErrorCode@
-- are @CLOUDFORMATION_STACK_INACTIVE@ and
-- @CLOUDFORMATION_STACK_NOT_EXISTING@.
--
-- 'resourceIdentifiers', 'searchResourcesResponse_resourceIdentifiers' - The ARNs and resource types of resources that are members of the group
-- that you specified.
--
-- 'httpStatus', 'searchResourcesResponse_httpStatus' - The response's http status code.
newSearchResourcesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  SearchResourcesResponse
newSearchResourcesResponse :: Int -> SearchResourcesResponse
newSearchResourcesResponse Int
pHttpStatus_ =
  SearchResourcesResponse'
    { $sel:nextToken:SearchResourcesResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:queryErrors:SearchResourcesResponse' :: Maybe [QueryError]
queryErrors = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceIdentifiers:SearchResourcesResponse' :: Maybe [ResourceIdentifier]
resourceIdentifiers = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:SearchResourcesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

-- | A list of @QueryError@ objects. Each error is an object that contains
-- @ErrorCode@ and @Message@ structures. Possible values for @ErrorCode@
-- are @CLOUDFORMATION_STACK_INACTIVE@ and
-- @CLOUDFORMATION_STACK_NOT_EXISTING@.
searchResourcesResponse_queryErrors :: Lens.Lens' SearchResourcesResponse (Prelude.Maybe [QueryError])
searchResourcesResponse_queryErrors :: Lens' SearchResourcesResponse (Maybe [QueryError])
searchResourcesResponse_queryErrors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchResourcesResponse' {Maybe [QueryError]
queryErrors :: Maybe [QueryError]
$sel:queryErrors:SearchResourcesResponse' :: SearchResourcesResponse -> Maybe [QueryError]
queryErrors} -> Maybe [QueryError]
queryErrors) (\s :: SearchResourcesResponse
s@SearchResourcesResponse' {} Maybe [QueryError]
a -> SearchResourcesResponse
s {$sel:queryErrors:SearchResourcesResponse' :: Maybe [QueryError]
queryErrors = Maybe [QueryError]
a} :: SearchResourcesResponse) 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 ARNs and resource types of resources that are members of the group
-- that you specified.
searchResourcesResponse_resourceIdentifiers :: Lens.Lens' SearchResourcesResponse (Prelude.Maybe [ResourceIdentifier])
searchResourcesResponse_resourceIdentifiers :: Lens' SearchResourcesResponse (Maybe [ResourceIdentifier])
searchResourcesResponse_resourceIdentifiers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchResourcesResponse' {Maybe [ResourceIdentifier]
resourceIdentifiers :: Maybe [ResourceIdentifier]
$sel:resourceIdentifiers:SearchResourcesResponse' :: SearchResourcesResponse -> Maybe [ResourceIdentifier]
resourceIdentifiers} -> Maybe [ResourceIdentifier]
resourceIdentifiers) (\s :: SearchResourcesResponse
s@SearchResourcesResponse' {} Maybe [ResourceIdentifier]
a -> SearchResourcesResponse
s {$sel:resourceIdentifiers:SearchResourcesResponse' :: Maybe [ResourceIdentifier]
resourceIdentifiers = Maybe [ResourceIdentifier]
a} :: SearchResourcesResponse) 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.
searchResourcesResponse_httpStatus :: Lens.Lens' SearchResourcesResponse Prelude.Int
searchResourcesResponse_httpStatus :: Lens' SearchResourcesResponse Int
searchResourcesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchResourcesResponse' {Int
httpStatus :: Int
$sel:httpStatus:SearchResourcesResponse' :: SearchResourcesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: SearchResourcesResponse
s@SearchResourcesResponse' {} Int
a -> SearchResourcesResponse
s {$sel:httpStatus:SearchResourcesResponse' :: Int
httpStatus = Int
a} :: SearchResourcesResponse)

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