{-# 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.Inspector2.ListFilters
-- 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 the filters associated with your account.
--
-- This operation returns paginated results.
module Amazonka.Inspector2.ListFilters
  ( -- * Creating a Request
    ListFilters (..),
    newListFilters,

    -- * Request Lenses
    listFilters_action,
    listFilters_arns,
    listFilters_maxResults,
    listFilters_nextToken,

    -- * Destructuring the Response
    ListFiltersResponse (..),
    newListFiltersResponse,

    -- * Response Lenses
    listFiltersResponse_nextToken,
    listFiltersResponse_httpStatus,
    listFiltersResponse_filters,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Inspector2.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newListFilters' smart constructor.
data ListFilters = ListFilters'
  { -- | The action the filter applies to matched findings.
    ListFilters -> Maybe FilterAction
action :: Prelude.Maybe FilterAction,
    -- | The Amazon resource number (ARN) of the filter.
    ListFilters -> Maybe [Text]
arns :: Prelude.Maybe [Prelude.Text],
    -- | The maximum number of results to return in the response.
    ListFilters -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | A token to use for paginating results that are returned in the response.
    -- Set the value of this parameter to null for the first request to a list
    -- action. For subsequent calls, use the @NextToken@ value returned from
    -- the previous request to continue listing results after the first page.
    ListFilters -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListFilters -> ListFilters -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListFilters -> ListFilters -> Bool
$c/= :: ListFilters -> ListFilters -> Bool
== :: ListFilters -> ListFilters -> Bool
$c== :: ListFilters -> ListFilters -> Bool
Prelude.Eq, ReadPrec [ListFilters]
ReadPrec ListFilters
Int -> ReadS ListFilters
ReadS [ListFilters]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListFilters]
$creadListPrec :: ReadPrec [ListFilters]
readPrec :: ReadPrec ListFilters
$creadPrec :: ReadPrec ListFilters
readList :: ReadS [ListFilters]
$creadList :: ReadS [ListFilters]
readsPrec :: Int -> ReadS ListFilters
$creadsPrec :: Int -> ReadS ListFilters
Prelude.Read, Int -> ListFilters -> ShowS
[ListFilters] -> ShowS
ListFilters -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListFilters] -> ShowS
$cshowList :: [ListFilters] -> ShowS
show :: ListFilters -> String
$cshow :: ListFilters -> String
showsPrec :: Int -> ListFilters -> ShowS
$cshowsPrec :: Int -> ListFilters -> ShowS
Prelude.Show, forall x. Rep ListFilters x -> ListFilters
forall x. ListFilters -> Rep ListFilters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListFilters x -> ListFilters
$cfrom :: forall x. ListFilters -> Rep ListFilters x
Prelude.Generic)

-- |
-- Create a value of 'ListFilters' 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:
--
-- 'action', 'listFilters_action' - The action the filter applies to matched findings.
--
-- 'arns', 'listFilters_arns' - The Amazon resource number (ARN) of the filter.
--
-- 'maxResults', 'listFilters_maxResults' - The maximum number of results to return in the response.
--
-- 'nextToken', 'listFilters_nextToken' - A token to use for paginating results that are returned in the response.
-- Set the value of this parameter to null for the first request to a list
-- action. For subsequent calls, use the @NextToken@ value returned from
-- the previous request to continue listing results after the first page.
newListFilters ::
  ListFilters
newListFilters :: ListFilters
newListFilters =
  ListFilters'
    { $sel:action:ListFilters' :: Maybe FilterAction
action = forall a. Maybe a
Prelude.Nothing,
      $sel:arns:ListFilters' :: Maybe [Text]
arns = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListFilters' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListFilters' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The action the filter applies to matched findings.
listFilters_action :: Lens.Lens' ListFilters (Prelude.Maybe FilterAction)
listFilters_action :: Lens' ListFilters (Maybe FilterAction)
listFilters_action = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFilters' {Maybe FilterAction
action :: Maybe FilterAction
$sel:action:ListFilters' :: ListFilters -> Maybe FilterAction
action} -> Maybe FilterAction
action) (\s :: ListFilters
s@ListFilters' {} Maybe FilterAction
a -> ListFilters
s {$sel:action:ListFilters' :: Maybe FilterAction
action = Maybe FilterAction
a} :: ListFilters)

-- | The Amazon resource number (ARN) of the filter.
listFilters_arns :: Lens.Lens' ListFilters (Prelude.Maybe [Prelude.Text])
listFilters_arns :: Lens' ListFilters (Maybe [Text])
listFilters_arns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFilters' {Maybe [Text]
arns :: Maybe [Text]
$sel:arns:ListFilters' :: ListFilters -> Maybe [Text]
arns} -> Maybe [Text]
arns) (\s :: ListFilters
s@ListFilters' {} Maybe [Text]
a -> ListFilters
s {$sel:arns:ListFilters' :: Maybe [Text]
arns = Maybe [Text]
a} :: ListFilters) 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 maximum number of results to return in the response.
listFilters_maxResults :: Lens.Lens' ListFilters (Prelude.Maybe Prelude.Natural)
listFilters_maxResults :: Lens' ListFilters (Maybe Natural)
listFilters_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFilters' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListFilters' :: ListFilters -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListFilters
s@ListFilters' {} Maybe Natural
a -> ListFilters
s {$sel:maxResults:ListFilters' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListFilters)

-- | A token to use for paginating results that are returned in the response.
-- Set the value of this parameter to null for the first request to a list
-- action. For subsequent calls, use the @NextToken@ value returned from
-- the previous request to continue listing results after the first page.
listFilters_nextToken :: Lens.Lens' ListFilters (Prelude.Maybe Prelude.Text)
listFilters_nextToken :: Lens' ListFilters (Maybe Text)
listFilters_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFilters' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListFilters' :: ListFilters -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListFilters
s@ListFilters' {} Maybe Text
a -> ListFilters
s {$sel:nextToken:ListFilters' :: Maybe Text
nextToken = Maybe Text
a} :: ListFilters)

instance Core.AWSPager ListFilters where
  page :: ListFilters -> AWSResponse ListFilters -> Maybe ListFilters
page ListFilters
rq AWSResponse ListFilters
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListFilters
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListFiltersResponse (Maybe Text)
listFiltersResponse_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 ListFilters
rs forall s a. s -> Getting a s a -> a
Lens.^. Lens' ListFiltersResponse [Filter]
listFiltersResponse_filters) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListFilters
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListFilters (Maybe Text)
listFilters_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListFilters
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListFiltersResponse (Maybe Text)
listFiltersResponse_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 ListFilters where
  type AWSResponse ListFilters = ListFiltersResponse
  request :: (Service -> Service) -> ListFilters -> Request ListFilters
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 ListFilters
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListFilters)))
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 -> Int -> [Filter] -> ListFiltersResponse
ListFiltersResponse'
            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
            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
"filters" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
      )

instance Prelude.Hashable ListFilters where
  hashWithSalt :: Int -> ListFilters -> Int
hashWithSalt Int
_salt ListFilters' {Maybe Natural
Maybe [Text]
Maybe Text
Maybe FilterAction
nextToken :: Maybe Text
maxResults :: Maybe Natural
arns :: Maybe [Text]
action :: Maybe FilterAction
$sel:nextToken:ListFilters' :: ListFilters -> Maybe Text
$sel:maxResults:ListFilters' :: ListFilters -> Maybe Natural
$sel:arns:ListFilters' :: ListFilters -> Maybe [Text]
$sel:action:ListFilters' :: ListFilters -> Maybe FilterAction
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FilterAction
action
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
arns
      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 ListFilters where
  rnf :: ListFilters -> ()
rnf ListFilters' {Maybe Natural
Maybe [Text]
Maybe Text
Maybe FilterAction
nextToken :: Maybe Text
maxResults :: Maybe Natural
arns :: Maybe [Text]
action :: Maybe FilterAction
$sel:nextToken:ListFilters' :: ListFilters -> Maybe Text
$sel:maxResults:ListFilters' :: ListFilters -> Maybe Natural
$sel:arns:ListFilters' :: ListFilters -> Maybe [Text]
$sel:action:ListFilters' :: ListFilters -> Maybe FilterAction
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe FilterAction
action
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
arns
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 ListFilters where
  toHeaders :: ListFilters -> 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 ListFilters where
  toJSON :: ListFilters -> Value
toJSON ListFilters' {Maybe Natural
Maybe [Text]
Maybe Text
Maybe FilterAction
nextToken :: Maybe Text
maxResults :: Maybe Natural
arns :: Maybe [Text]
action :: Maybe FilterAction
$sel:nextToken:ListFilters' :: ListFilters -> Maybe Text
$sel:maxResults:ListFilters' :: ListFilters -> Maybe Natural
$sel:arns:ListFilters' :: ListFilters -> Maybe [Text]
$sel:action:ListFilters' :: ListFilters -> Maybe FilterAction
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"action" 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 FilterAction
action,
            (Key
"arns" 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]
arns,
            (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 ListFilters where
  toPath :: ListFilters -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/filters/list"

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

-- | /See:/ 'newListFiltersResponse' smart constructor.
data ListFiltersResponse = ListFiltersResponse'
  { -- | A token to use for paginating results that are returned in the response.
    -- Set the value of this parameter to null for the first request to a list
    -- action. For subsequent calls, use the @NextToken@ value returned from
    -- the previous request to continue listing results after the first page.
    ListFiltersResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListFiltersResponse -> Int
httpStatus :: Prelude.Int,
    -- | Contains details on the filters associated with your account.
    ListFiltersResponse -> [Filter]
filters :: [Filter]
  }
  deriving (ListFiltersResponse -> ListFiltersResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListFiltersResponse -> ListFiltersResponse -> Bool
$c/= :: ListFiltersResponse -> ListFiltersResponse -> Bool
== :: ListFiltersResponse -> ListFiltersResponse -> Bool
$c== :: ListFiltersResponse -> ListFiltersResponse -> Bool
Prelude.Eq, ReadPrec [ListFiltersResponse]
ReadPrec ListFiltersResponse
Int -> ReadS ListFiltersResponse
ReadS [ListFiltersResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListFiltersResponse]
$creadListPrec :: ReadPrec [ListFiltersResponse]
readPrec :: ReadPrec ListFiltersResponse
$creadPrec :: ReadPrec ListFiltersResponse
readList :: ReadS [ListFiltersResponse]
$creadList :: ReadS [ListFiltersResponse]
readsPrec :: Int -> ReadS ListFiltersResponse
$creadsPrec :: Int -> ReadS ListFiltersResponse
Prelude.Read, Int -> ListFiltersResponse -> ShowS
[ListFiltersResponse] -> ShowS
ListFiltersResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListFiltersResponse] -> ShowS
$cshowList :: [ListFiltersResponse] -> ShowS
show :: ListFiltersResponse -> String
$cshow :: ListFiltersResponse -> String
showsPrec :: Int -> ListFiltersResponse -> ShowS
$cshowsPrec :: Int -> ListFiltersResponse -> ShowS
Prelude.Show, forall x. Rep ListFiltersResponse x -> ListFiltersResponse
forall x. ListFiltersResponse -> Rep ListFiltersResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListFiltersResponse x -> ListFiltersResponse
$cfrom :: forall x. ListFiltersResponse -> Rep ListFiltersResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListFiltersResponse' 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', 'listFiltersResponse_nextToken' - A token to use for paginating results that are returned in the response.
-- Set the value of this parameter to null for the first request to a list
-- action. For subsequent calls, use the @NextToken@ value returned from
-- the previous request to continue listing results after the first page.
--
-- 'httpStatus', 'listFiltersResponse_httpStatus' - The response's http status code.
--
-- 'filters', 'listFiltersResponse_filters' - Contains details on the filters associated with your account.
newListFiltersResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListFiltersResponse
newListFiltersResponse :: Int -> ListFiltersResponse
newListFiltersResponse Int
pHttpStatus_ =
  ListFiltersResponse'
    { $sel:nextToken:ListFiltersResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListFiltersResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:filters:ListFiltersResponse' :: [Filter]
filters = forall a. Monoid a => a
Prelude.mempty
    }

-- | A token to use for paginating results that are returned in the response.
-- Set the value of this parameter to null for the first request to a list
-- action. For subsequent calls, use the @NextToken@ value returned from
-- the previous request to continue listing results after the first page.
listFiltersResponse_nextToken :: Lens.Lens' ListFiltersResponse (Prelude.Maybe Prelude.Text)
listFiltersResponse_nextToken :: Lens' ListFiltersResponse (Maybe Text)
listFiltersResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFiltersResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListFiltersResponse' :: ListFiltersResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListFiltersResponse
s@ListFiltersResponse' {} Maybe Text
a -> ListFiltersResponse
s {$sel:nextToken:ListFiltersResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListFiltersResponse)

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

-- | Contains details on the filters associated with your account.
listFiltersResponse_filters :: Lens.Lens' ListFiltersResponse [Filter]
listFiltersResponse_filters :: Lens' ListFiltersResponse [Filter]
listFiltersResponse_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFiltersResponse' {[Filter]
filters :: [Filter]
$sel:filters:ListFiltersResponse' :: ListFiltersResponse -> [Filter]
filters} -> [Filter]
filters) (\s :: ListFiltersResponse
s@ListFiltersResponse' {} [Filter]
a -> ListFiltersResponse
s {$sel:filters:ListFiltersResponse' :: [Filter]
filters = [Filter]
a} :: ListFiltersResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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