{-# 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.AccessAnalyzer.ListAnalyzers
-- 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 a list of analyzers.
--
-- This operation returns paginated results.
module Amazonka.AccessAnalyzer.ListAnalyzers
  ( -- * Creating a Request
    ListAnalyzers (..),
    newListAnalyzers,

    -- * Request Lenses
    listAnalyzers_maxResults,
    listAnalyzers_nextToken,
    listAnalyzers_type,

    -- * Destructuring the Response
    ListAnalyzersResponse (..),
    newListAnalyzersResponse,

    -- * Response Lenses
    listAnalyzersResponse_nextToken,
    listAnalyzersResponse_httpStatus,
    listAnalyzersResponse_analyzers,
  )
where

import Amazonka.AccessAnalyzer.Types
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

-- | Retrieves a list of analyzers.
--
-- /See:/ 'newListAnalyzers' smart constructor.
data ListAnalyzers = ListAnalyzers'
  { -- | The maximum number of results to return in the response.
    ListAnalyzers -> Maybe Int
maxResults :: Prelude.Maybe Prelude.Int,
    -- | A token used for pagination of results returned.
    ListAnalyzers -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The type of analyzer.
    ListAnalyzers -> Maybe Type
type' :: Prelude.Maybe Type
  }
  deriving (ListAnalyzers -> ListAnalyzers -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAnalyzers -> ListAnalyzers -> Bool
$c/= :: ListAnalyzers -> ListAnalyzers -> Bool
== :: ListAnalyzers -> ListAnalyzers -> Bool
$c== :: ListAnalyzers -> ListAnalyzers -> Bool
Prelude.Eq, ReadPrec [ListAnalyzers]
ReadPrec ListAnalyzers
Int -> ReadS ListAnalyzers
ReadS [ListAnalyzers]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAnalyzers]
$creadListPrec :: ReadPrec [ListAnalyzers]
readPrec :: ReadPrec ListAnalyzers
$creadPrec :: ReadPrec ListAnalyzers
readList :: ReadS [ListAnalyzers]
$creadList :: ReadS [ListAnalyzers]
readsPrec :: Int -> ReadS ListAnalyzers
$creadsPrec :: Int -> ReadS ListAnalyzers
Prelude.Read, Int -> ListAnalyzers -> ShowS
[ListAnalyzers] -> ShowS
ListAnalyzers -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAnalyzers] -> ShowS
$cshowList :: [ListAnalyzers] -> ShowS
show :: ListAnalyzers -> String
$cshow :: ListAnalyzers -> String
showsPrec :: Int -> ListAnalyzers -> ShowS
$cshowsPrec :: Int -> ListAnalyzers -> ShowS
Prelude.Show, forall x. Rep ListAnalyzers x -> ListAnalyzers
forall x. ListAnalyzers -> Rep ListAnalyzers x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListAnalyzers x -> ListAnalyzers
$cfrom :: forall x. ListAnalyzers -> Rep ListAnalyzers x
Prelude.Generic)

-- |
-- Create a value of 'ListAnalyzers' 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', 'listAnalyzers_maxResults' - The maximum number of results to return in the response.
--
-- 'nextToken', 'listAnalyzers_nextToken' - A token used for pagination of results returned.
--
-- 'type'', 'listAnalyzers_type' - The type of analyzer.
newListAnalyzers ::
  ListAnalyzers
newListAnalyzers :: ListAnalyzers
newListAnalyzers =
  ListAnalyzers'
    { $sel:maxResults:ListAnalyzers' :: Maybe Int
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListAnalyzers' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:type':ListAnalyzers' :: Maybe Type
type' = forall a. Maybe a
Prelude.Nothing
    }

-- | The maximum number of results to return in the response.
listAnalyzers_maxResults :: Lens.Lens' ListAnalyzers (Prelude.Maybe Prelude.Int)
listAnalyzers_maxResults :: Lens' ListAnalyzers (Maybe Int)
listAnalyzers_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAnalyzers' {Maybe Int
maxResults :: Maybe Int
$sel:maxResults:ListAnalyzers' :: ListAnalyzers -> Maybe Int
maxResults} -> Maybe Int
maxResults) (\s :: ListAnalyzers
s@ListAnalyzers' {} Maybe Int
a -> ListAnalyzers
s {$sel:maxResults:ListAnalyzers' :: Maybe Int
maxResults = Maybe Int
a} :: ListAnalyzers)

-- | A token used for pagination of results returned.
listAnalyzers_nextToken :: Lens.Lens' ListAnalyzers (Prelude.Maybe Prelude.Text)
listAnalyzers_nextToken :: Lens' ListAnalyzers (Maybe Text)
listAnalyzers_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAnalyzers' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAnalyzers' :: ListAnalyzers -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAnalyzers
s@ListAnalyzers' {} Maybe Text
a -> ListAnalyzers
s {$sel:nextToken:ListAnalyzers' :: Maybe Text
nextToken = Maybe Text
a} :: ListAnalyzers)

-- | The type of analyzer.
listAnalyzers_type :: Lens.Lens' ListAnalyzers (Prelude.Maybe Type)
listAnalyzers_type :: Lens' ListAnalyzers (Maybe Type)
listAnalyzers_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAnalyzers' {Maybe Type
type' :: Maybe Type
$sel:type':ListAnalyzers' :: ListAnalyzers -> Maybe Type
type'} -> Maybe Type
type') (\s :: ListAnalyzers
s@ListAnalyzers' {} Maybe Type
a -> ListAnalyzers
s {$sel:type':ListAnalyzers' :: Maybe Type
type' = Maybe Type
a} :: ListAnalyzers)

instance Core.AWSPager ListAnalyzers where
  page :: ListAnalyzers -> AWSResponse ListAnalyzers -> Maybe ListAnalyzers
page ListAnalyzers
rq AWSResponse ListAnalyzers
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListAnalyzers
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAnalyzersResponse (Maybe Text)
listAnalyzersResponse_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 ListAnalyzers
rs forall s a. s -> Getting a s a -> a
Lens.^. Lens' ListAnalyzersResponse [AnalyzerSummary]
listAnalyzersResponse_analyzers) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListAnalyzers
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListAnalyzers (Maybe Text)
listAnalyzers_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListAnalyzers
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAnalyzersResponse (Maybe Text)
listAnalyzersResponse_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 ListAnalyzers where
  type
    AWSResponse ListAnalyzers =
      ListAnalyzersResponse
  request :: (Service -> Service) -> ListAnalyzers -> Request ListAnalyzers
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListAnalyzers
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListAnalyzers)))
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 -> [AnalyzerSummary] -> ListAnalyzersResponse
ListAnalyzersResponse'
            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
"analyzers" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
      )

instance Prelude.Hashable ListAnalyzers where
  hashWithSalt :: Int -> ListAnalyzers -> Int
hashWithSalt Int
_salt ListAnalyzers' {Maybe Int
Maybe Text
Maybe Type
type' :: Maybe Type
nextToken :: Maybe Text
maxResults :: Maybe Int
$sel:type':ListAnalyzers' :: ListAnalyzers -> Maybe Type
$sel:nextToken:ListAnalyzers' :: ListAnalyzers -> Maybe Text
$sel:maxResults:ListAnalyzers' :: ListAnalyzers -> Maybe Int
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Type
type'

instance Prelude.NFData ListAnalyzers where
  rnf :: ListAnalyzers -> ()
rnf ListAnalyzers' {Maybe Int
Maybe Text
Maybe Type
type' :: Maybe Type
nextToken :: Maybe Text
maxResults :: Maybe Int
$sel:type':ListAnalyzers' :: ListAnalyzers -> Maybe Type
$sel:nextToken:ListAnalyzers' :: ListAnalyzers -> Maybe Text
$sel:maxResults:ListAnalyzers' :: ListAnalyzers -> Maybe Int
..} =
    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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Type
type'

instance Data.ToHeaders ListAnalyzers where
  toHeaders :: ListAnalyzers -> 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.ToPath ListAnalyzers where
  toPath :: ListAnalyzers -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/analyzer"

instance Data.ToQuery ListAnalyzers where
  toQuery :: ListAnalyzers -> QueryString
toQuery ListAnalyzers' {Maybe Int
Maybe Text
Maybe Type
type' :: Maybe Type
nextToken :: Maybe Text
maxResults :: Maybe Int
$sel:type':ListAnalyzers' :: ListAnalyzers -> Maybe Type
$sel:nextToken:ListAnalyzers' :: ListAnalyzers -> Maybe Text
$sel:maxResults:ListAnalyzers' :: ListAnalyzers -> Maybe Int
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"maxResults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
maxResults,
        ByteString
"nextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken,
        ByteString
"type" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Type
type'
      ]

-- | The response to the request.
--
-- /See:/ 'newListAnalyzersResponse' smart constructor.
data ListAnalyzersResponse = ListAnalyzersResponse'
  { -- | A token used for pagination of results returned.
    ListAnalyzersResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListAnalyzersResponse -> Int
httpStatus :: Prelude.Int,
    -- | The analyzers retrieved.
    ListAnalyzersResponse -> [AnalyzerSummary]
analyzers :: [AnalyzerSummary]
  }
  deriving (ListAnalyzersResponse -> ListAnalyzersResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAnalyzersResponse -> ListAnalyzersResponse -> Bool
$c/= :: ListAnalyzersResponse -> ListAnalyzersResponse -> Bool
== :: ListAnalyzersResponse -> ListAnalyzersResponse -> Bool
$c== :: ListAnalyzersResponse -> ListAnalyzersResponse -> Bool
Prelude.Eq, ReadPrec [ListAnalyzersResponse]
ReadPrec ListAnalyzersResponse
Int -> ReadS ListAnalyzersResponse
ReadS [ListAnalyzersResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAnalyzersResponse]
$creadListPrec :: ReadPrec [ListAnalyzersResponse]
readPrec :: ReadPrec ListAnalyzersResponse
$creadPrec :: ReadPrec ListAnalyzersResponse
readList :: ReadS [ListAnalyzersResponse]
$creadList :: ReadS [ListAnalyzersResponse]
readsPrec :: Int -> ReadS ListAnalyzersResponse
$creadsPrec :: Int -> ReadS ListAnalyzersResponse
Prelude.Read, Int -> ListAnalyzersResponse -> ShowS
[ListAnalyzersResponse] -> ShowS
ListAnalyzersResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAnalyzersResponse] -> ShowS
$cshowList :: [ListAnalyzersResponse] -> ShowS
show :: ListAnalyzersResponse -> String
$cshow :: ListAnalyzersResponse -> String
showsPrec :: Int -> ListAnalyzersResponse -> ShowS
$cshowsPrec :: Int -> ListAnalyzersResponse -> ShowS
Prelude.Show, forall x. Rep ListAnalyzersResponse x -> ListAnalyzersResponse
forall x. ListAnalyzersResponse -> Rep ListAnalyzersResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListAnalyzersResponse x -> ListAnalyzersResponse
$cfrom :: forall x. ListAnalyzersResponse -> Rep ListAnalyzersResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListAnalyzersResponse' 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', 'listAnalyzersResponse_nextToken' - A token used for pagination of results returned.
--
-- 'httpStatus', 'listAnalyzersResponse_httpStatus' - The response's http status code.
--
-- 'analyzers', 'listAnalyzersResponse_analyzers' - The analyzers retrieved.
newListAnalyzersResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListAnalyzersResponse
newListAnalyzersResponse :: Int -> ListAnalyzersResponse
newListAnalyzersResponse Int
pHttpStatus_ =
  ListAnalyzersResponse'
    { $sel:nextToken:ListAnalyzersResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListAnalyzersResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:analyzers:ListAnalyzersResponse' :: [AnalyzerSummary]
analyzers = forall a. Monoid a => a
Prelude.mempty
    }

-- | A token used for pagination of results returned.
listAnalyzersResponse_nextToken :: Lens.Lens' ListAnalyzersResponse (Prelude.Maybe Prelude.Text)
listAnalyzersResponse_nextToken :: Lens' ListAnalyzersResponse (Maybe Text)
listAnalyzersResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAnalyzersResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAnalyzersResponse' :: ListAnalyzersResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAnalyzersResponse
s@ListAnalyzersResponse' {} Maybe Text
a -> ListAnalyzersResponse
s {$sel:nextToken:ListAnalyzersResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListAnalyzersResponse)

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

-- | The analyzers retrieved.
listAnalyzersResponse_analyzers :: Lens.Lens' ListAnalyzersResponse [AnalyzerSummary]
listAnalyzersResponse_analyzers :: Lens' ListAnalyzersResponse [AnalyzerSummary]
listAnalyzersResponse_analyzers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAnalyzersResponse' {[AnalyzerSummary]
analyzers :: [AnalyzerSummary]
$sel:analyzers:ListAnalyzersResponse' :: ListAnalyzersResponse -> [AnalyzerSummary]
analyzers} -> [AnalyzerSummary]
analyzers) (\s :: ListAnalyzersResponse
s@ListAnalyzersResponse' {} [AnalyzerSummary]
a -> ListAnalyzersResponse
s {$sel:analyzers:ListAnalyzersResponse' :: [AnalyzerSummary]
analyzers = [AnalyzerSummary]
a} :: ListAnalyzersResponse) 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 ListAnalyzersResponse where
  rnf :: ListAnalyzersResponse -> ()
rnf ListAnalyzersResponse' {Int
[AnalyzerSummary]
Maybe Text
analyzers :: [AnalyzerSummary]
httpStatus :: Int
nextToken :: Maybe Text
$sel:analyzers:ListAnalyzersResponse' :: ListAnalyzersResponse -> [AnalyzerSummary]
$sel:httpStatus:ListAnalyzersResponse' :: ListAnalyzersResponse -> Int
$sel:nextToken:ListAnalyzersResponse' :: ListAnalyzersResponse -> 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 [AnalyzerSummary]
analyzers