{-# 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.RobOMaker.ListWorlds
-- 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 worlds.
--
-- This operation returns paginated results.
module Amazonka.RobOMaker.ListWorlds
  ( -- * Creating a Request
    ListWorlds (..),
    newListWorlds,

    -- * Request Lenses
    listWorlds_filters,
    listWorlds_maxResults,
    listWorlds_nextToken,

    -- * Destructuring the Response
    ListWorldsResponse (..),
    newListWorldsResponse,

    -- * Response Lenses
    listWorldsResponse_nextToken,
    listWorldsResponse_worldSummaries,
    listWorldsResponse_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 qualified Amazonka.Response as Response
import Amazonka.RobOMaker.Types

-- | /See:/ 'newListWorlds' smart constructor.
data ListWorlds = ListWorlds'
  { -- | Optional filters to limit results. You can use @status@.
    ListWorlds -> Maybe (NonEmpty Filter)
filters :: Prelude.Maybe (Prelude.NonEmpty Filter),
    -- | When this parameter is used, @ListWorlds@ only returns @maxResults@
    -- results in a single page along with a @nextToken@ response element. The
    -- remaining results of the initial request can be seen by sending another
    -- @ListWorlds@ request with the returned @nextToken@ value. This value can
    -- be between 1 and 100. If this parameter is not used, then @ListWorlds@
    -- returns up to 100 results and a @nextToken@ value if applicable.
    ListWorlds -> Maybe Int
maxResults :: Prelude.Maybe Prelude.Int,
    -- | If the previous paginated request did not 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 @ListWorlds@ 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.
    ListWorlds -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListWorlds -> ListWorlds -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListWorlds -> ListWorlds -> Bool
$c/= :: ListWorlds -> ListWorlds -> Bool
== :: ListWorlds -> ListWorlds -> Bool
$c== :: ListWorlds -> ListWorlds -> Bool
Prelude.Eq, ReadPrec [ListWorlds]
ReadPrec ListWorlds
Int -> ReadS ListWorlds
ReadS [ListWorlds]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListWorlds]
$creadListPrec :: ReadPrec [ListWorlds]
readPrec :: ReadPrec ListWorlds
$creadPrec :: ReadPrec ListWorlds
readList :: ReadS [ListWorlds]
$creadList :: ReadS [ListWorlds]
readsPrec :: Int -> ReadS ListWorlds
$creadsPrec :: Int -> ReadS ListWorlds
Prelude.Read, Int -> ListWorlds -> ShowS
[ListWorlds] -> ShowS
ListWorlds -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListWorlds] -> ShowS
$cshowList :: [ListWorlds] -> ShowS
show :: ListWorlds -> String
$cshow :: ListWorlds -> String
showsPrec :: Int -> ListWorlds -> ShowS
$cshowsPrec :: Int -> ListWorlds -> ShowS
Prelude.Show, forall x. Rep ListWorlds x -> ListWorlds
forall x. ListWorlds -> Rep ListWorlds x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListWorlds x -> ListWorlds
$cfrom :: forall x. ListWorlds -> Rep ListWorlds x
Prelude.Generic)

-- |
-- Create a value of 'ListWorlds' 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', 'listWorlds_filters' - Optional filters to limit results. You can use @status@.
--
-- 'maxResults', 'listWorlds_maxResults' - When this parameter is used, @ListWorlds@ only returns @maxResults@
-- results in a single page along with a @nextToken@ response element. The
-- remaining results of the initial request can be seen by sending another
-- @ListWorlds@ request with the returned @nextToken@ value. This value can
-- be between 1 and 100. If this parameter is not used, then @ListWorlds@
-- returns up to 100 results and a @nextToken@ value if applicable.
--
-- 'nextToken', 'listWorlds_nextToken' - If the previous paginated request did not 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 @ListWorlds@ 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.
newListWorlds ::
  ListWorlds
newListWorlds :: ListWorlds
newListWorlds =
  ListWorlds'
    { $sel:filters:ListWorlds' :: Maybe (NonEmpty Filter)
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListWorlds' :: Maybe Int
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListWorlds' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | Optional filters to limit results. You can use @status@.
listWorlds_filters :: Lens.Lens' ListWorlds (Prelude.Maybe (Prelude.NonEmpty Filter))
listWorlds_filters :: Lens' ListWorlds (Maybe (NonEmpty Filter))
listWorlds_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListWorlds' {Maybe (NonEmpty Filter)
filters :: Maybe (NonEmpty Filter)
$sel:filters:ListWorlds' :: ListWorlds -> Maybe (NonEmpty Filter)
filters} -> Maybe (NonEmpty Filter)
filters) (\s :: ListWorlds
s@ListWorlds' {} Maybe (NonEmpty Filter)
a -> ListWorlds
s {$sel:filters:ListWorlds' :: Maybe (NonEmpty Filter)
filters = Maybe (NonEmpty Filter)
a} :: ListWorlds) 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

-- | When this parameter is used, @ListWorlds@ only returns @maxResults@
-- results in a single page along with a @nextToken@ response element. The
-- remaining results of the initial request can be seen by sending another
-- @ListWorlds@ request with the returned @nextToken@ value. This value can
-- be between 1 and 100. If this parameter is not used, then @ListWorlds@
-- returns up to 100 results and a @nextToken@ value if applicable.
listWorlds_maxResults :: Lens.Lens' ListWorlds (Prelude.Maybe Prelude.Int)
listWorlds_maxResults :: Lens' ListWorlds (Maybe Int)
listWorlds_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListWorlds' {Maybe Int
maxResults :: Maybe Int
$sel:maxResults:ListWorlds' :: ListWorlds -> Maybe Int
maxResults} -> Maybe Int
maxResults) (\s :: ListWorlds
s@ListWorlds' {} Maybe Int
a -> ListWorlds
s {$sel:maxResults:ListWorlds' :: Maybe Int
maxResults = Maybe Int
a} :: ListWorlds)

-- | If the previous paginated request did not 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 @ListWorlds@ 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.
listWorlds_nextToken :: Lens.Lens' ListWorlds (Prelude.Maybe Prelude.Text)
listWorlds_nextToken :: Lens' ListWorlds (Maybe Text)
listWorlds_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListWorlds' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListWorlds' :: ListWorlds -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListWorlds
s@ListWorlds' {} Maybe Text
a -> ListWorlds
s {$sel:nextToken:ListWorlds' :: Maybe Text
nextToken = Maybe Text
a} :: ListWorlds)

instance Core.AWSPager ListWorlds where
  page :: ListWorlds -> AWSResponse ListWorlds -> Maybe ListWorlds
page ListWorlds
rq AWSResponse ListWorlds
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListWorlds
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListWorldsResponse (Maybe Text)
listWorldsResponse_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 ListWorlds
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListWorldsResponse (Maybe [WorldSummary])
listWorldsResponse_worldSummaries
            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.$ ListWorlds
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListWorlds (Maybe Text)
listWorlds_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListWorlds
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListWorldsResponse (Maybe Text)
listWorldsResponse_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 ListWorlds where
  type AWSResponse ListWorlds = ListWorldsResponse
  request :: (Service -> Service) -> ListWorlds -> Request ListWorlds
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 ListWorlds
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListWorlds)))
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 [WorldSummary] -> Int -> ListWorldsResponse
ListWorldsResponse'
            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
"worldSummaries" 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 ListWorlds where
  hashWithSalt :: Int -> ListWorlds -> Int
hashWithSalt Int
_salt ListWorlds' {Maybe Int
Maybe (NonEmpty Filter)
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
filters :: Maybe (NonEmpty Filter)
$sel:nextToken:ListWorlds' :: ListWorlds -> Maybe Text
$sel:maxResults:ListWorlds' :: ListWorlds -> Maybe Int
$sel:filters:ListWorlds' :: ListWorlds -> Maybe (NonEmpty Filter)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Filter)
filters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData ListWorlds where
  rnf :: ListWorlds -> ()
rnf ListWorlds' {Maybe Int
Maybe (NonEmpty Filter)
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
filters :: Maybe (NonEmpty Filter)
$sel:nextToken:ListWorlds' :: ListWorlds -> Maybe Text
$sel:maxResults:ListWorlds' :: ListWorlds -> Maybe Int
$sel:filters:ListWorlds' :: ListWorlds -> Maybe (NonEmpty Filter)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Filter)
filters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken

instance Data.ToHeaders ListWorlds where
  toHeaders :: ListWorlds -> 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 ListWorlds where
  toJSON :: ListWorlds -> Value
toJSON ListWorlds' {Maybe Int
Maybe (NonEmpty Filter)
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
filters :: Maybe (NonEmpty Filter)
$sel:nextToken:ListWorlds' :: ListWorlds -> Maybe Text
$sel:maxResults:ListWorlds' :: ListWorlds -> Maybe Int
$sel:filters:ListWorlds' :: ListWorlds -> Maybe (NonEmpty Filter)
..} =
    [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 (NonEmpty Filter)
filters,
            (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 Int
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
          ]
      )

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

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

-- | /See:/ 'newListWorldsResponse' smart constructor.
data ListWorldsResponse = ListWorldsResponse'
  { -- | If the previous paginated request did not 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 @ListWorlds@ 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.
    ListWorldsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Summary information for worlds.
    ListWorldsResponse -> Maybe [WorldSummary]
worldSummaries :: Prelude.Maybe [WorldSummary],
    -- | The response's http status code.
    ListWorldsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListWorldsResponse -> ListWorldsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListWorldsResponse -> ListWorldsResponse -> Bool
$c/= :: ListWorldsResponse -> ListWorldsResponse -> Bool
== :: ListWorldsResponse -> ListWorldsResponse -> Bool
$c== :: ListWorldsResponse -> ListWorldsResponse -> Bool
Prelude.Eq, ReadPrec [ListWorldsResponse]
ReadPrec ListWorldsResponse
Int -> ReadS ListWorldsResponse
ReadS [ListWorldsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListWorldsResponse]
$creadListPrec :: ReadPrec [ListWorldsResponse]
readPrec :: ReadPrec ListWorldsResponse
$creadPrec :: ReadPrec ListWorldsResponse
readList :: ReadS [ListWorldsResponse]
$creadList :: ReadS [ListWorldsResponse]
readsPrec :: Int -> ReadS ListWorldsResponse
$creadsPrec :: Int -> ReadS ListWorldsResponse
Prelude.Read, Int -> ListWorldsResponse -> ShowS
[ListWorldsResponse] -> ShowS
ListWorldsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListWorldsResponse] -> ShowS
$cshowList :: [ListWorldsResponse] -> ShowS
show :: ListWorldsResponse -> String
$cshow :: ListWorldsResponse -> String
showsPrec :: Int -> ListWorldsResponse -> ShowS
$cshowsPrec :: Int -> ListWorldsResponse -> ShowS
Prelude.Show, forall x. Rep ListWorldsResponse x -> ListWorldsResponse
forall x. ListWorldsResponse -> Rep ListWorldsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListWorldsResponse x -> ListWorldsResponse
$cfrom :: forall x. ListWorldsResponse -> Rep ListWorldsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListWorldsResponse' 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', 'listWorldsResponse_nextToken' - If the previous paginated request did not 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 @ListWorlds@ 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.
--
-- 'worldSummaries', 'listWorldsResponse_worldSummaries' - Summary information for worlds.
--
-- 'httpStatus', 'listWorldsResponse_httpStatus' - The response's http status code.
newListWorldsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListWorldsResponse
newListWorldsResponse :: Int -> ListWorldsResponse
newListWorldsResponse Int
pHttpStatus_ =
  ListWorldsResponse'
    { $sel:nextToken:ListWorldsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:worldSummaries:ListWorldsResponse' :: Maybe [WorldSummary]
worldSummaries = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListWorldsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | If the previous paginated request did not 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 @ListWorlds@ 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.
listWorldsResponse_nextToken :: Lens.Lens' ListWorldsResponse (Prelude.Maybe Prelude.Text)
listWorldsResponse_nextToken :: Lens' ListWorldsResponse (Maybe Text)
listWorldsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListWorldsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListWorldsResponse' :: ListWorldsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListWorldsResponse
s@ListWorldsResponse' {} Maybe Text
a -> ListWorldsResponse
s {$sel:nextToken:ListWorldsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListWorldsResponse)

-- | Summary information for worlds.
listWorldsResponse_worldSummaries :: Lens.Lens' ListWorldsResponse (Prelude.Maybe [WorldSummary])
listWorldsResponse_worldSummaries :: Lens' ListWorldsResponse (Maybe [WorldSummary])
listWorldsResponse_worldSummaries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListWorldsResponse' {Maybe [WorldSummary]
worldSummaries :: Maybe [WorldSummary]
$sel:worldSummaries:ListWorldsResponse' :: ListWorldsResponse -> Maybe [WorldSummary]
worldSummaries} -> Maybe [WorldSummary]
worldSummaries) (\s :: ListWorldsResponse
s@ListWorldsResponse' {} Maybe [WorldSummary]
a -> ListWorldsResponse
s {$sel:worldSummaries:ListWorldsResponse' :: Maybe [WorldSummary]
worldSummaries = Maybe [WorldSummary]
a} :: ListWorldsResponse) 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.
listWorldsResponse_httpStatus :: Lens.Lens' ListWorldsResponse Prelude.Int
listWorldsResponse_httpStatus :: Lens' ListWorldsResponse Int
listWorldsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListWorldsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListWorldsResponse' :: ListWorldsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListWorldsResponse
s@ListWorldsResponse' {} Int
a -> ListWorldsResponse
s {$sel:httpStatus:ListWorldsResponse' :: Int
httpStatus = Int
a} :: ListWorldsResponse)

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