{-# 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.WAF.ListRateBasedRules
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This is __AWS WAF Classic__ documentation. For more information, see
-- <https://docs.aws.amazon.com/waf/latest/developerguide/classic-waf-chapter.html AWS WAF Classic>
-- in the developer guide.
--
-- __For the latest version of AWS WAF__, use the AWS WAFV2 API and see the
-- <https://docs.aws.amazon.com/waf/latest/developerguide/waf-chapter.html AWS WAF Developer Guide>.
-- With the latest version, AWS WAF has a single set of endpoints for
-- regional and global use.
--
-- Returns an array of RuleSummary objects.
--
-- This operation returns paginated results.
module Amazonka.WAF.ListRateBasedRules
  ( -- * Creating a Request
    ListRateBasedRules (..),
    newListRateBasedRules,

    -- * Request Lenses
    listRateBasedRules_limit,
    listRateBasedRules_nextMarker,

    -- * Destructuring the Response
    ListRateBasedRulesResponse (..),
    newListRateBasedRulesResponse,

    -- * Response Lenses
    listRateBasedRulesResponse_nextMarker,
    listRateBasedRulesResponse_rules,
    listRateBasedRulesResponse_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.WAF.Types

-- | /See:/ 'newListRateBasedRules' smart constructor.
data ListRateBasedRules = ListRateBasedRules'
  { -- | Specifies the number of @Rules@ that you want AWS WAF to return for this
    -- request. If you have more @Rules@ than the number that you specify for
    -- @Limit@, the response includes a @NextMarker@ value that you can use to
    -- get another batch of @Rules@.
    ListRateBasedRules -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
    -- | If you specify a value for @Limit@ and you have more @Rules@ than the
    -- value of @Limit@, AWS WAF returns a @NextMarker@ value in the response
    -- that allows you to list another group of @Rules@. For the second and
    -- subsequent @ListRateBasedRules@ requests, specify the value of
    -- @NextMarker@ from the previous response to get information about another
    -- batch of @Rules@.
    ListRateBasedRules -> Maybe Text
nextMarker :: Prelude.Maybe Prelude.Text
  }
  deriving (ListRateBasedRules -> ListRateBasedRules -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListRateBasedRules -> ListRateBasedRules -> Bool
$c/= :: ListRateBasedRules -> ListRateBasedRules -> Bool
== :: ListRateBasedRules -> ListRateBasedRules -> Bool
$c== :: ListRateBasedRules -> ListRateBasedRules -> Bool
Prelude.Eq, ReadPrec [ListRateBasedRules]
ReadPrec ListRateBasedRules
Int -> ReadS ListRateBasedRules
ReadS [ListRateBasedRules]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListRateBasedRules]
$creadListPrec :: ReadPrec [ListRateBasedRules]
readPrec :: ReadPrec ListRateBasedRules
$creadPrec :: ReadPrec ListRateBasedRules
readList :: ReadS [ListRateBasedRules]
$creadList :: ReadS [ListRateBasedRules]
readsPrec :: Int -> ReadS ListRateBasedRules
$creadsPrec :: Int -> ReadS ListRateBasedRules
Prelude.Read, Int -> ListRateBasedRules -> ShowS
[ListRateBasedRules] -> ShowS
ListRateBasedRules -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListRateBasedRules] -> ShowS
$cshowList :: [ListRateBasedRules] -> ShowS
show :: ListRateBasedRules -> String
$cshow :: ListRateBasedRules -> String
showsPrec :: Int -> ListRateBasedRules -> ShowS
$cshowsPrec :: Int -> ListRateBasedRules -> ShowS
Prelude.Show, forall x. Rep ListRateBasedRules x -> ListRateBasedRules
forall x. ListRateBasedRules -> Rep ListRateBasedRules x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListRateBasedRules x -> ListRateBasedRules
$cfrom :: forall x. ListRateBasedRules -> Rep ListRateBasedRules x
Prelude.Generic)

-- |
-- Create a value of 'ListRateBasedRules' 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:
--
-- 'limit', 'listRateBasedRules_limit' - Specifies the number of @Rules@ that you want AWS WAF to return for this
-- request. If you have more @Rules@ than the number that you specify for
-- @Limit@, the response includes a @NextMarker@ value that you can use to
-- get another batch of @Rules@.
--
-- 'nextMarker', 'listRateBasedRules_nextMarker' - If you specify a value for @Limit@ and you have more @Rules@ than the
-- value of @Limit@, AWS WAF returns a @NextMarker@ value in the response
-- that allows you to list another group of @Rules@. For the second and
-- subsequent @ListRateBasedRules@ requests, specify the value of
-- @NextMarker@ from the previous response to get information about another
-- batch of @Rules@.
newListRateBasedRules ::
  ListRateBasedRules
newListRateBasedRules :: ListRateBasedRules
newListRateBasedRules =
  ListRateBasedRules'
    { $sel:limit:ListRateBasedRules' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:nextMarker:ListRateBasedRules' :: Maybe Text
nextMarker = forall a. Maybe a
Prelude.Nothing
    }

-- | Specifies the number of @Rules@ that you want AWS WAF to return for this
-- request. If you have more @Rules@ than the number that you specify for
-- @Limit@, the response includes a @NextMarker@ value that you can use to
-- get another batch of @Rules@.
listRateBasedRules_limit :: Lens.Lens' ListRateBasedRules (Prelude.Maybe Prelude.Natural)
listRateBasedRules_limit :: Lens' ListRateBasedRules (Maybe Natural)
listRateBasedRules_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRateBasedRules' {Maybe Natural
limit :: Maybe Natural
$sel:limit:ListRateBasedRules' :: ListRateBasedRules -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: ListRateBasedRules
s@ListRateBasedRules' {} Maybe Natural
a -> ListRateBasedRules
s {$sel:limit:ListRateBasedRules' :: Maybe Natural
limit = Maybe Natural
a} :: ListRateBasedRules)

-- | If you specify a value for @Limit@ and you have more @Rules@ than the
-- value of @Limit@, AWS WAF returns a @NextMarker@ value in the response
-- that allows you to list another group of @Rules@. For the second and
-- subsequent @ListRateBasedRules@ requests, specify the value of
-- @NextMarker@ from the previous response to get information about another
-- batch of @Rules@.
listRateBasedRules_nextMarker :: Lens.Lens' ListRateBasedRules (Prelude.Maybe Prelude.Text)
listRateBasedRules_nextMarker :: Lens' ListRateBasedRules (Maybe Text)
listRateBasedRules_nextMarker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRateBasedRules' {Maybe Text
nextMarker :: Maybe Text
$sel:nextMarker:ListRateBasedRules' :: ListRateBasedRules -> Maybe Text
nextMarker} -> Maybe Text
nextMarker) (\s :: ListRateBasedRules
s@ListRateBasedRules' {} Maybe Text
a -> ListRateBasedRules
s {$sel:nextMarker:ListRateBasedRules' :: Maybe Text
nextMarker = Maybe Text
a} :: ListRateBasedRules)

instance Core.AWSPager ListRateBasedRules where
  page :: ListRateBasedRules
-> AWSResponse ListRateBasedRules -> Maybe ListRateBasedRules
page ListRateBasedRules
rq AWSResponse ListRateBasedRules
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListRateBasedRules
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListRateBasedRulesResponse (Maybe Text)
listRateBasedRulesResponse_nextMarker
            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 ListRateBasedRules
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListRateBasedRulesResponse (Maybe [RuleSummary])
listRateBasedRulesResponse_rules
            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.$ ListRateBasedRules
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListRateBasedRules (Maybe Text)
listRateBasedRules_nextMarker
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListRateBasedRules
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListRateBasedRulesResponse (Maybe Text)
listRateBasedRulesResponse_nextMarker
          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 ListRateBasedRules where
  type
    AWSResponse ListRateBasedRules =
      ListRateBasedRulesResponse
  request :: (Service -> Service)
-> ListRateBasedRules -> Request ListRateBasedRules
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 ListRateBasedRules
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListRateBasedRules)))
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 [RuleSummary] -> Int -> ListRateBasedRulesResponse
ListRateBasedRulesResponse'
            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
"NextMarker")
            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
"Rules" 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 ListRateBasedRules where
  hashWithSalt :: Int -> ListRateBasedRules -> Int
hashWithSalt Int
_salt ListRateBasedRules' {Maybe Natural
Maybe Text
nextMarker :: Maybe Text
limit :: Maybe Natural
$sel:nextMarker:ListRateBasedRules' :: ListRateBasedRules -> Maybe Text
$sel:limit:ListRateBasedRules' :: ListRateBasedRules -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
limit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextMarker

instance Prelude.NFData ListRateBasedRules where
  rnf :: ListRateBasedRules -> ()
rnf ListRateBasedRules' {Maybe Natural
Maybe Text
nextMarker :: Maybe Text
limit :: Maybe Natural
$sel:nextMarker:ListRateBasedRules' :: ListRateBasedRules -> Maybe Text
$sel:limit:ListRateBasedRules' :: ListRateBasedRules -> Maybe Natural
..} =
    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
nextMarker

instance Data.ToHeaders ListRateBasedRules where
  toHeaders :: ListRateBasedRules -> 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
"AWSWAF_20150824.ListRateBasedRules" ::
                          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 ListRateBasedRules where
  toJSON :: ListRateBasedRules -> Value
toJSON ListRateBasedRules' {Maybe Natural
Maybe Text
nextMarker :: Maybe Text
limit :: Maybe Natural
$sel:nextMarker:ListRateBasedRules' :: ListRateBasedRules -> Maybe Text
$sel:limit:ListRateBasedRules' :: ListRateBasedRules -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (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
"NextMarker" 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
nextMarker
          ]
      )

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

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

-- | /See:/ 'newListRateBasedRulesResponse' smart constructor.
data ListRateBasedRulesResponse = ListRateBasedRulesResponse'
  { -- | If you have more @Rules@ than the number that you specified for @Limit@
    -- in the request, the response includes a @NextMarker@ value. To list more
    -- @Rules@, submit another @ListRateBasedRules@ request, and specify the
    -- @NextMarker@ value from the response in the @NextMarker@ value in the
    -- next request.
    ListRateBasedRulesResponse -> Maybe Text
nextMarker :: Prelude.Maybe Prelude.Text,
    -- | An array of RuleSummary objects.
    ListRateBasedRulesResponse -> Maybe [RuleSummary]
rules :: Prelude.Maybe [RuleSummary],
    -- | The response's http status code.
    ListRateBasedRulesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListRateBasedRulesResponse -> ListRateBasedRulesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListRateBasedRulesResponse -> ListRateBasedRulesResponse -> Bool
$c/= :: ListRateBasedRulesResponse -> ListRateBasedRulesResponse -> Bool
== :: ListRateBasedRulesResponse -> ListRateBasedRulesResponse -> Bool
$c== :: ListRateBasedRulesResponse -> ListRateBasedRulesResponse -> Bool
Prelude.Eq, ReadPrec [ListRateBasedRulesResponse]
ReadPrec ListRateBasedRulesResponse
Int -> ReadS ListRateBasedRulesResponse
ReadS [ListRateBasedRulesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListRateBasedRulesResponse]
$creadListPrec :: ReadPrec [ListRateBasedRulesResponse]
readPrec :: ReadPrec ListRateBasedRulesResponse
$creadPrec :: ReadPrec ListRateBasedRulesResponse
readList :: ReadS [ListRateBasedRulesResponse]
$creadList :: ReadS [ListRateBasedRulesResponse]
readsPrec :: Int -> ReadS ListRateBasedRulesResponse
$creadsPrec :: Int -> ReadS ListRateBasedRulesResponse
Prelude.Read, Int -> ListRateBasedRulesResponse -> ShowS
[ListRateBasedRulesResponse] -> ShowS
ListRateBasedRulesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListRateBasedRulesResponse] -> ShowS
$cshowList :: [ListRateBasedRulesResponse] -> ShowS
show :: ListRateBasedRulesResponse -> String
$cshow :: ListRateBasedRulesResponse -> String
showsPrec :: Int -> ListRateBasedRulesResponse -> ShowS
$cshowsPrec :: Int -> ListRateBasedRulesResponse -> ShowS
Prelude.Show, forall x.
Rep ListRateBasedRulesResponse x -> ListRateBasedRulesResponse
forall x.
ListRateBasedRulesResponse -> Rep ListRateBasedRulesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListRateBasedRulesResponse x -> ListRateBasedRulesResponse
$cfrom :: forall x.
ListRateBasedRulesResponse -> Rep ListRateBasedRulesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListRateBasedRulesResponse' 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:
--
-- 'nextMarker', 'listRateBasedRulesResponse_nextMarker' - If you have more @Rules@ than the number that you specified for @Limit@
-- in the request, the response includes a @NextMarker@ value. To list more
-- @Rules@, submit another @ListRateBasedRules@ request, and specify the
-- @NextMarker@ value from the response in the @NextMarker@ value in the
-- next request.
--
-- 'rules', 'listRateBasedRulesResponse_rules' - An array of RuleSummary objects.
--
-- 'httpStatus', 'listRateBasedRulesResponse_httpStatus' - The response's http status code.
newListRateBasedRulesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListRateBasedRulesResponse
newListRateBasedRulesResponse :: Int -> ListRateBasedRulesResponse
newListRateBasedRulesResponse Int
pHttpStatus_ =
  ListRateBasedRulesResponse'
    { $sel:nextMarker:ListRateBasedRulesResponse' :: Maybe Text
nextMarker =
        forall a. Maybe a
Prelude.Nothing,
      $sel:rules:ListRateBasedRulesResponse' :: Maybe [RuleSummary]
rules = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListRateBasedRulesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | If you have more @Rules@ than the number that you specified for @Limit@
-- in the request, the response includes a @NextMarker@ value. To list more
-- @Rules@, submit another @ListRateBasedRules@ request, and specify the
-- @NextMarker@ value from the response in the @NextMarker@ value in the
-- next request.
listRateBasedRulesResponse_nextMarker :: Lens.Lens' ListRateBasedRulesResponse (Prelude.Maybe Prelude.Text)
listRateBasedRulesResponse_nextMarker :: Lens' ListRateBasedRulesResponse (Maybe Text)
listRateBasedRulesResponse_nextMarker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRateBasedRulesResponse' {Maybe Text
nextMarker :: Maybe Text
$sel:nextMarker:ListRateBasedRulesResponse' :: ListRateBasedRulesResponse -> Maybe Text
nextMarker} -> Maybe Text
nextMarker) (\s :: ListRateBasedRulesResponse
s@ListRateBasedRulesResponse' {} Maybe Text
a -> ListRateBasedRulesResponse
s {$sel:nextMarker:ListRateBasedRulesResponse' :: Maybe Text
nextMarker = Maybe Text
a} :: ListRateBasedRulesResponse)

-- | An array of RuleSummary objects.
listRateBasedRulesResponse_rules :: Lens.Lens' ListRateBasedRulesResponse (Prelude.Maybe [RuleSummary])
listRateBasedRulesResponse_rules :: Lens' ListRateBasedRulesResponse (Maybe [RuleSummary])
listRateBasedRulesResponse_rules = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRateBasedRulesResponse' {Maybe [RuleSummary]
rules :: Maybe [RuleSummary]
$sel:rules:ListRateBasedRulesResponse' :: ListRateBasedRulesResponse -> Maybe [RuleSummary]
rules} -> Maybe [RuleSummary]
rules) (\s :: ListRateBasedRulesResponse
s@ListRateBasedRulesResponse' {} Maybe [RuleSummary]
a -> ListRateBasedRulesResponse
s {$sel:rules:ListRateBasedRulesResponse' :: Maybe [RuleSummary]
rules = Maybe [RuleSummary]
a} :: ListRateBasedRulesResponse) 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.
listRateBasedRulesResponse_httpStatus :: Lens.Lens' ListRateBasedRulesResponse Prelude.Int
listRateBasedRulesResponse_httpStatus :: Lens' ListRateBasedRulesResponse Int
listRateBasedRulesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRateBasedRulesResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListRateBasedRulesResponse' :: ListRateBasedRulesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListRateBasedRulesResponse
s@ListRateBasedRulesResponse' {} Int
a -> ListRateBasedRulesResponse
s {$sel:httpStatus:ListRateBasedRulesResponse' :: Int
httpStatus = Int
a} :: ListRateBasedRulesResponse)

instance Prelude.NFData ListRateBasedRulesResponse where
  rnf :: ListRateBasedRulesResponse -> ()
rnf ListRateBasedRulesResponse' {Int
Maybe [RuleSummary]
Maybe Text
httpStatus :: Int
rules :: Maybe [RuleSummary]
nextMarker :: Maybe Text
$sel:httpStatus:ListRateBasedRulesResponse' :: ListRateBasedRulesResponse -> Int
$sel:rules:ListRateBasedRulesResponse' :: ListRateBasedRulesResponse -> Maybe [RuleSummary]
$sel:nextMarker:ListRateBasedRulesResponse' :: ListRateBasedRulesResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextMarker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [RuleSummary]
rules
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus