{-# 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.Route53Resolver.ListFirewallDomainLists
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves the firewall domain lists that you have defined. For each
-- firewall domain list, you can retrieve the domains that are defined for
-- a list by calling ListFirewallDomains.
--
-- A single call to this list operation might return only a partial list of
-- the domain lists. For information, see @MaxResults@.
--
-- This operation returns paginated results.
module Amazonka.Route53Resolver.ListFirewallDomainLists
  ( -- * Creating a Request
    ListFirewallDomainLists (..),
    newListFirewallDomainLists,

    -- * Request Lenses
    listFirewallDomainLists_maxResults,
    listFirewallDomainLists_nextToken,

    -- * Destructuring the Response
    ListFirewallDomainListsResponse (..),
    newListFirewallDomainListsResponse,

    -- * Response Lenses
    listFirewallDomainListsResponse_firewallDomainLists,
    listFirewallDomainListsResponse_nextToken,
    listFirewallDomainListsResponse_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.Route53Resolver.Types

-- | /See:/ 'newListFirewallDomainLists' smart constructor.
data ListFirewallDomainLists = ListFirewallDomainLists'
  { -- | The maximum number of objects that you want Resolver to return for this
    -- request. If more objects are available, in the response, Resolver
    -- provides a @NextToken@ value that you can use in a subsequent call to
    -- get the next batch of objects.
    --
    -- If you don\'t specify a value for @MaxResults@, Resolver returns up to
    -- 100 objects.
    ListFirewallDomainLists -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | For the first call to this list request, omit this value.
    --
    -- When you request a list of objects, Resolver returns at most the number
    -- of objects specified in @MaxResults@. If more objects are available for
    -- retrieval, Resolver returns a @NextToken@ value in the response. To
    -- retrieve the next batch of objects, use the token that was returned for
    -- the prior request in your next request.
    ListFirewallDomainLists -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListFirewallDomainLists -> ListFirewallDomainLists -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListFirewallDomainLists -> ListFirewallDomainLists -> Bool
$c/= :: ListFirewallDomainLists -> ListFirewallDomainLists -> Bool
== :: ListFirewallDomainLists -> ListFirewallDomainLists -> Bool
$c== :: ListFirewallDomainLists -> ListFirewallDomainLists -> Bool
Prelude.Eq, ReadPrec [ListFirewallDomainLists]
ReadPrec ListFirewallDomainLists
Int -> ReadS ListFirewallDomainLists
ReadS [ListFirewallDomainLists]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListFirewallDomainLists]
$creadListPrec :: ReadPrec [ListFirewallDomainLists]
readPrec :: ReadPrec ListFirewallDomainLists
$creadPrec :: ReadPrec ListFirewallDomainLists
readList :: ReadS [ListFirewallDomainLists]
$creadList :: ReadS [ListFirewallDomainLists]
readsPrec :: Int -> ReadS ListFirewallDomainLists
$creadsPrec :: Int -> ReadS ListFirewallDomainLists
Prelude.Read, Int -> ListFirewallDomainLists -> ShowS
[ListFirewallDomainLists] -> ShowS
ListFirewallDomainLists -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListFirewallDomainLists] -> ShowS
$cshowList :: [ListFirewallDomainLists] -> ShowS
show :: ListFirewallDomainLists -> String
$cshow :: ListFirewallDomainLists -> String
showsPrec :: Int -> ListFirewallDomainLists -> ShowS
$cshowsPrec :: Int -> ListFirewallDomainLists -> ShowS
Prelude.Show, forall x. Rep ListFirewallDomainLists x -> ListFirewallDomainLists
forall x. ListFirewallDomainLists -> Rep ListFirewallDomainLists x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListFirewallDomainLists x -> ListFirewallDomainLists
$cfrom :: forall x. ListFirewallDomainLists -> Rep ListFirewallDomainLists x
Prelude.Generic)

-- |
-- Create a value of 'ListFirewallDomainLists' 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', 'listFirewallDomainLists_maxResults' - The maximum number of objects that you want Resolver to return for this
-- request. If more objects are available, in the response, Resolver
-- provides a @NextToken@ value that you can use in a subsequent call to
-- get the next batch of objects.
--
-- If you don\'t specify a value for @MaxResults@, Resolver returns up to
-- 100 objects.
--
-- 'nextToken', 'listFirewallDomainLists_nextToken' - For the first call to this list request, omit this value.
--
-- When you request a list of objects, Resolver returns at most the number
-- of objects specified in @MaxResults@. If more objects are available for
-- retrieval, Resolver returns a @NextToken@ value in the response. To
-- retrieve the next batch of objects, use the token that was returned for
-- the prior request in your next request.
newListFirewallDomainLists ::
  ListFirewallDomainLists
newListFirewallDomainLists :: ListFirewallDomainLists
newListFirewallDomainLists =
  ListFirewallDomainLists'
    { $sel:maxResults:ListFirewallDomainLists' :: Maybe Natural
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListFirewallDomainLists' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The maximum number of objects that you want Resolver to return for this
-- request. If more objects are available, in the response, Resolver
-- provides a @NextToken@ value that you can use in a subsequent call to
-- get the next batch of objects.
--
-- If you don\'t specify a value for @MaxResults@, Resolver returns up to
-- 100 objects.
listFirewallDomainLists_maxResults :: Lens.Lens' ListFirewallDomainLists (Prelude.Maybe Prelude.Natural)
listFirewallDomainLists_maxResults :: Lens' ListFirewallDomainLists (Maybe Natural)
listFirewallDomainLists_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFirewallDomainLists' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListFirewallDomainLists' :: ListFirewallDomainLists -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListFirewallDomainLists
s@ListFirewallDomainLists' {} Maybe Natural
a -> ListFirewallDomainLists
s {$sel:maxResults:ListFirewallDomainLists' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListFirewallDomainLists)

-- | For the first call to this list request, omit this value.
--
-- When you request a list of objects, Resolver returns at most the number
-- of objects specified in @MaxResults@. If more objects are available for
-- retrieval, Resolver returns a @NextToken@ value in the response. To
-- retrieve the next batch of objects, use the token that was returned for
-- the prior request in your next request.
listFirewallDomainLists_nextToken :: Lens.Lens' ListFirewallDomainLists (Prelude.Maybe Prelude.Text)
listFirewallDomainLists_nextToken :: Lens' ListFirewallDomainLists (Maybe Text)
listFirewallDomainLists_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFirewallDomainLists' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListFirewallDomainLists' :: ListFirewallDomainLists -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListFirewallDomainLists
s@ListFirewallDomainLists' {} Maybe Text
a -> ListFirewallDomainLists
s {$sel:nextToken:ListFirewallDomainLists' :: Maybe Text
nextToken = Maybe Text
a} :: ListFirewallDomainLists)

instance Core.AWSPager ListFirewallDomainLists where
  page :: ListFirewallDomainLists
-> AWSResponse ListFirewallDomainLists
-> Maybe ListFirewallDomainLists
page ListFirewallDomainLists
rq AWSResponse ListFirewallDomainLists
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListFirewallDomainLists
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListFirewallDomainListsResponse (Maybe Text)
listFirewallDomainListsResponse_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 ListFirewallDomainLists
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  ListFirewallDomainListsResponse
  (Maybe [FirewallDomainListMetadata])
listFirewallDomainListsResponse_firewallDomainLists
            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.$ ListFirewallDomainLists
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListFirewallDomainLists (Maybe Text)
listFirewallDomainLists_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListFirewallDomainLists
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListFirewallDomainListsResponse (Maybe Text)
listFirewallDomainListsResponse_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 ListFirewallDomainLists where
  type
    AWSResponse ListFirewallDomainLists =
      ListFirewallDomainListsResponse
  request :: (Service -> Service)
-> ListFirewallDomainLists -> Request ListFirewallDomainLists
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 ListFirewallDomainLists
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListFirewallDomainLists)))
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 [FirewallDomainListMetadata]
-> Maybe Text -> Int -> ListFirewallDomainListsResponse
ListFirewallDomainListsResponse'
            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
"FirewallDomainLists"
                            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
"NextToken")
            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 ListFirewallDomainLists where
  hashWithSalt :: Int -> ListFirewallDomainLists -> Int
hashWithSalt Int
_salt ListFirewallDomainLists' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListFirewallDomainLists' :: ListFirewallDomainLists -> Maybe Text
$sel:maxResults:ListFirewallDomainLists' :: ListFirewallDomainLists -> 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

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

instance Data.ToHeaders ListFirewallDomainLists where
  toHeaders :: ListFirewallDomainLists -> 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
"Route53Resolver.ListFirewallDomainLists" ::
                          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 ListFirewallDomainLists where
  toJSON :: ListFirewallDomainLists -> Value
toJSON ListFirewallDomainLists' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListFirewallDomainLists' :: ListFirewallDomainLists -> Maybe Text
$sel:maxResults:ListFirewallDomainLists' :: ListFirewallDomainLists -> 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
          ]
      )

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

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

-- | /See:/ 'newListFirewallDomainListsResponse' smart constructor.
data ListFirewallDomainListsResponse = ListFirewallDomainListsResponse'
  { -- | A list of the domain lists that you have defined.
    --
    -- This might be a partial list of the domain lists that you\'ve defined.
    -- For information, see @MaxResults@.
    ListFirewallDomainListsResponse
-> Maybe [FirewallDomainListMetadata]
firewallDomainLists :: Prelude.Maybe [FirewallDomainListMetadata],
    -- | If objects are still available for retrieval, Resolver returns this
    -- token in the response. To retrieve the next batch of objects, provide
    -- this token in your next request.
    ListFirewallDomainListsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListFirewallDomainListsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListFirewallDomainListsResponse
-> ListFirewallDomainListsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListFirewallDomainListsResponse
-> ListFirewallDomainListsResponse -> Bool
$c/= :: ListFirewallDomainListsResponse
-> ListFirewallDomainListsResponse -> Bool
== :: ListFirewallDomainListsResponse
-> ListFirewallDomainListsResponse -> Bool
$c== :: ListFirewallDomainListsResponse
-> ListFirewallDomainListsResponse -> Bool
Prelude.Eq, ReadPrec [ListFirewallDomainListsResponse]
ReadPrec ListFirewallDomainListsResponse
Int -> ReadS ListFirewallDomainListsResponse
ReadS [ListFirewallDomainListsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListFirewallDomainListsResponse]
$creadListPrec :: ReadPrec [ListFirewallDomainListsResponse]
readPrec :: ReadPrec ListFirewallDomainListsResponse
$creadPrec :: ReadPrec ListFirewallDomainListsResponse
readList :: ReadS [ListFirewallDomainListsResponse]
$creadList :: ReadS [ListFirewallDomainListsResponse]
readsPrec :: Int -> ReadS ListFirewallDomainListsResponse
$creadsPrec :: Int -> ReadS ListFirewallDomainListsResponse
Prelude.Read, Int -> ListFirewallDomainListsResponse -> ShowS
[ListFirewallDomainListsResponse] -> ShowS
ListFirewallDomainListsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListFirewallDomainListsResponse] -> ShowS
$cshowList :: [ListFirewallDomainListsResponse] -> ShowS
show :: ListFirewallDomainListsResponse -> String
$cshow :: ListFirewallDomainListsResponse -> String
showsPrec :: Int -> ListFirewallDomainListsResponse -> ShowS
$cshowsPrec :: Int -> ListFirewallDomainListsResponse -> ShowS
Prelude.Show, forall x.
Rep ListFirewallDomainListsResponse x
-> ListFirewallDomainListsResponse
forall x.
ListFirewallDomainListsResponse
-> Rep ListFirewallDomainListsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListFirewallDomainListsResponse x
-> ListFirewallDomainListsResponse
$cfrom :: forall x.
ListFirewallDomainListsResponse
-> Rep ListFirewallDomainListsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListFirewallDomainListsResponse' 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:
--
-- 'firewallDomainLists', 'listFirewallDomainListsResponse_firewallDomainLists' - A list of the domain lists that you have defined.
--
-- This might be a partial list of the domain lists that you\'ve defined.
-- For information, see @MaxResults@.
--
-- 'nextToken', 'listFirewallDomainListsResponse_nextToken' - If objects are still available for retrieval, Resolver returns this
-- token in the response. To retrieve the next batch of objects, provide
-- this token in your next request.
--
-- 'httpStatus', 'listFirewallDomainListsResponse_httpStatus' - The response's http status code.
newListFirewallDomainListsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListFirewallDomainListsResponse
newListFirewallDomainListsResponse :: Int -> ListFirewallDomainListsResponse
newListFirewallDomainListsResponse Int
pHttpStatus_ =
  ListFirewallDomainListsResponse'
    { $sel:firewallDomainLists:ListFirewallDomainListsResponse' :: Maybe [FirewallDomainListMetadata]
firewallDomainLists =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListFirewallDomainListsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListFirewallDomainListsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of the domain lists that you have defined.
--
-- This might be a partial list of the domain lists that you\'ve defined.
-- For information, see @MaxResults@.
listFirewallDomainListsResponse_firewallDomainLists :: Lens.Lens' ListFirewallDomainListsResponse (Prelude.Maybe [FirewallDomainListMetadata])
listFirewallDomainListsResponse_firewallDomainLists :: Lens'
  ListFirewallDomainListsResponse
  (Maybe [FirewallDomainListMetadata])
listFirewallDomainListsResponse_firewallDomainLists = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFirewallDomainListsResponse' {Maybe [FirewallDomainListMetadata]
firewallDomainLists :: Maybe [FirewallDomainListMetadata]
$sel:firewallDomainLists:ListFirewallDomainListsResponse' :: ListFirewallDomainListsResponse
-> Maybe [FirewallDomainListMetadata]
firewallDomainLists} -> Maybe [FirewallDomainListMetadata]
firewallDomainLists) (\s :: ListFirewallDomainListsResponse
s@ListFirewallDomainListsResponse' {} Maybe [FirewallDomainListMetadata]
a -> ListFirewallDomainListsResponse
s {$sel:firewallDomainLists:ListFirewallDomainListsResponse' :: Maybe [FirewallDomainListMetadata]
firewallDomainLists = Maybe [FirewallDomainListMetadata]
a} :: ListFirewallDomainListsResponse) 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

-- | If objects are still available for retrieval, Resolver returns this
-- token in the response. To retrieve the next batch of objects, provide
-- this token in your next request.
listFirewallDomainListsResponse_nextToken :: Lens.Lens' ListFirewallDomainListsResponse (Prelude.Maybe Prelude.Text)
listFirewallDomainListsResponse_nextToken :: Lens' ListFirewallDomainListsResponse (Maybe Text)
listFirewallDomainListsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFirewallDomainListsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListFirewallDomainListsResponse' :: ListFirewallDomainListsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListFirewallDomainListsResponse
s@ListFirewallDomainListsResponse' {} Maybe Text
a -> ListFirewallDomainListsResponse
s {$sel:nextToken:ListFirewallDomainListsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListFirewallDomainListsResponse)

-- | The response's http status code.
listFirewallDomainListsResponse_httpStatus :: Lens.Lens' ListFirewallDomainListsResponse Prelude.Int
listFirewallDomainListsResponse_httpStatus :: Lens' ListFirewallDomainListsResponse Int
listFirewallDomainListsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFirewallDomainListsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListFirewallDomainListsResponse' :: ListFirewallDomainListsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListFirewallDomainListsResponse
s@ListFirewallDomainListsResponse' {} Int
a -> ListFirewallDomainListsResponse
s {$sel:httpStatus:ListFirewallDomainListsResponse' :: Int
httpStatus = Int
a} :: ListFirewallDomainListsResponse)

instance
  Prelude.NFData
    ListFirewallDomainListsResponse
  where
  rnf :: ListFirewallDomainListsResponse -> ()
rnf ListFirewallDomainListsResponse' {Int
Maybe [FirewallDomainListMetadata]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
firewallDomainLists :: Maybe [FirewallDomainListMetadata]
$sel:httpStatus:ListFirewallDomainListsResponse' :: ListFirewallDomainListsResponse -> Int
$sel:nextToken:ListFirewallDomainListsResponse' :: ListFirewallDomainListsResponse -> Maybe Text
$sel:firewallDomainLists:ListFirewallDomainListsResponse' :: ListFirewallDomainListsResponse
-> Maybe [FirewallDomainListMetadata]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [FirewallDomainListMetadata]
firewallDomainLists
      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 Int
httpStatus