{-# 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.ListPolicyGenerations
-- 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 all of the policy generations requested in the last seven days.
--
-- This operation returns paginated results.
module Amazonka.AccessAnalyzer.ListPolicyGenerations
  ( -- * Creating a Request
    ListPolicyGenerations (..),
    newListPolicyGenerations,

    -- * Request Lenses
    listPolicyGenerations_maxResults,
    listPolicyGenerations_nextToken,
    listPolicyGenerations_principalArn,

    -- * Destructuring the Response
    ListPolicyGenerationsResponse (..),
    newListPolicyGenerationsResponse,

    -- * Response Lenses
    listPolicyGenerationsResponse_nextToken,
    listPolicyGenerationsResponse_httpStatus,
    listPolicyGenerationsResponse_policyGenerations,
  )
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

-- | /See:/ 'newListPolicyGenerations' smart constructor.
data ListPolicyGenerations = ListPolicyGenerations'
  { -- | The maximum number of results to return in the response.
    ListPolicyGenerations -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | A token used for pagination of results returned.
    ListPolicyGenerations -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The ARN of the IAM entity (user or role) for which you are generating a
    -- policy. Use this with @ListGeneratedPolicies@ to filter the results to
    -- only include results for a specific principal.
    ListPolicyGenerations -> Maybe Text
principalArn :: Prelude.Maybe Prelude.Text
  }
  deriving (ListPolicyGenerations -> ListPolicyGenerations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPolicyGenerations -> ListPolicyGenerations -> Bool
$c/= :: ListPolicyGenerations -> ListPolicyGenerations -> Bool
== :: ListPolicyGenerations -> ListPolicyGenerations -> Bool
$c== :: ListPolicyGenerations -> ListPolicyGenerations -> Bool
Prelude.Eq, ReadPrec [ListPolicyGenerations]
ReadPrec ListPolicyGenerations
Int -> ReadS ListPolicyGenerations
ReadS [ListPolicyGenerations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPolicyGenerations]
$creadListPrec :: ReadPrec [ListPolicyGenerations]
readPrec :: ReadPrec ListPolicyGenerations
$creadPrec :: ReadPrec ListPolicyGenerations
readList :: ReadS [ListPolicyGenerations]
$creadList :: ReadS [ListPolicyGenerations]
readsPrec :: Int -> ReadS ListPolicyGenerations
$creadsPrec :: Int -> ReadS ListPolicyGenerations
Prelude.Read, Int -> ListPolicyGenerations -> ShowS
[ListPolicyGenerations] -> ShowS
ListPolicyGenerations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPolicyGenerations] -> ShowS
$cshowList :: [ListPolicyGenerations] -> ShowS
show :: ListPolicyGenerations -> String
$cshow :: ListPolicyGenerations -> String
showsPrec :: Int -> ListPolicyGenerations -> ShowS
$cshowsPrec :: Int -> ListPolicyGenerations -> ShowS
Prelude.Show, forall x. Rep ListPolicyGenerations x -> ListPolicyGenerations
forall x. ListPolicyGenerations -> Rep ListPolicyGenerations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListPolicyGenerations x -> ListPolicyGenerations
$cfrom :: forall x. ListPolicyGenerations -> Rep ListPolicyGenerations x
Prelude.Generic)

-- |
-- Create a value of 'ListPolicyGenerations' 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', 'listPolicyGenerations_maxResults' - The maximum number of results to return in the response.
--
-- 'nextToken', 'listPolicyGenerations_nextToken' - A token used for pagination of results returned.
--
-- 'principalArn', 'listPolicyGenerations_principalArn' - The ARN of the IAM entity (user or role) for which you are generating a
-- policy. Use this with @ListGeneratedPolicies@ to filter the results to
-- only include results for a specific principal.
newListPolicyGenerations ::
  ListPolicyGenerations
newListPolicyGenerations :: ListPolicyGenerations
newListPolicyGenerations =
  ListPolicyGenerations'
    { $sel:maxResults:ListPolicyGenerations' :: Maybe Natural
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListPolicyGenerations' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:principalArn:ListPolicyGenerations' :: Maybe Text
principalArn = forall a. Maybe a
Prelude.Nothing
    }

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

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

-- | The ARN of the IAM entity (user or role) for which you are generating a
-- policy. Use this with @ListGeneratedPolicies@ to filter the results to
-- only include results for a specific principal.
listPolicyGenerations_principalArn :: Lens.Lens' ListPolicyGenerations (Prelude.Maybe Prelude.Text)
listPolicyGenerations_principalArn :: Lens' ListPolicyGenerations (Maybe Text)
listPolicyGenerations_principalArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPolicyGenerations' {Maybe Text
principalArn :: Maybe Text
$sel:principalArn:ListPolicyGenerations' :: ListPolicyGenerations -> Maybe Text
principalArn} -> Maybe Text
principalArn) (\s :: ListPolicyGenerations
s@ListPolicyGenerations' {} Maybe Text
a -> ListPolicyGenerations
s {$sel:principalArn:ListPolicyGenerations' :: Maybe Text
principalArn = Maybe Text
a} :: ListPolicyGenerations)

instance Core.AWSPager ListPolicyGenerations where
  page :: ListPolicyGenerations
-> AWSResponse ListPolicyGenerations -> Maybe ListPolicyGenerations
page ListPolicyGenerations
rq AWSResponse ListPolicyGenerations
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListPolicyGenerations
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListPolicyGenerationsResponse (Maybe Text)
listPolicyGenerationsResponse_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 ListPolicyGenerations
rs
            forall s a. s -> Getting a s a -> a
Lens.^. Lens' ListPolicyGenerationsResponse [PolicyGeneration]
listPolicyGenerationsResponse_policyGenerations
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListPolicyGenerations
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListPolicyGenerations (Maybe Text)
listPolicyGenerations_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListPolicyGenerations
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListPolicyGenerationsResponse (Maybe Text)
listPolicyGenerationsResponse_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 ListPolicyGenerations where
  type
    AWSResponse ListPolicyGenerations =
      ListPolicyGenerationsResponse
  request :: (Service -> Service)
-> ListPolicyGenerations -> Request ListPolicyGenerations
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 ListPolicyGenerations
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListPolicyGenerations)))
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 -> [PolicyGeneration] -> ListPolicyGenerationsResponse
ListPolicyGenerationsResponse'
            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
"policyGenerations"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
      )

instance Prelude.Hashable ListPolicyGenerations where
  hashWithSalt :: Int -> ListPolicyGenerations -> Int
hashWithSalt Int
_salt ListPolicyGenerations' {Maybe Natural
Maybe Text
principalArn :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:principalArn:ListPolicyGenerations' :: ListPolicyGenerations -> Maybe Text
$sel:nextToken:ListPolicyGenerations' :: ListPolicyGenerations -> Maybe Text
$sel:maxResults:ListPolicyGenerations' :: ListPolicyGenerations -> 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
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
principalArn

instance Prelude.NFData ListPolicyGenerations where
  rnf :: ListPolicyGenerations -> ()
rnf ListPolicyGenerations' {Maybe Natural
Maybe Text
principalArn :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:principalArn:ListPolicyGenerations' :: ListPolicyGenerations -> Maybe Text
$sel:nextToken:ListPolicyGenerations' :: ListPolicyGenerations -> Maybe Text
$sel:maxResults:ListPolicyGenerations' :: ListPolicyGenerations -> 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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
principalArn

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

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

-- | /See:/ 'newListPolicyGenerationsResponse' smart constructor.
data ListPolicyGenerationsResponse = ListPolicyGenerationsResponse'
  { -- | A token used for pagination of results returned.
    ListPolicyGenerationsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListPolicyGenerationsResponse -> Int
httpStatus :: Prelude.Int,
    -- | A @PolicyGeneration@ object that contains details about the generated
    -- policy.
    ListPolicyGenerationsResponse -> [PolicyGeneration]
policyGenerations :: [PolicyGeneration]
  }
  deriving (ListPolicyGenerationsResponse
-> ListPolicyGenerationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPolicyGenerationsResponse
-> ListPolicyGenerationsResponse -> Bool
$c/= :: ListPolicyGenerationsResponse
-> ListPolicyGenerationsResponse -> Bool
== :: ListPolicyGenerationsResponse
-> ListPolicyGenerationsResponse -> Bool
$c== :: ListPolicyGenerationsResponse
-> ListPolicyGenerationsResponse -> Bool
Prelude.Eq, ReadPrec [ListPolicyGenerationsResponse]
ReadPrec ListPolicyGenerationsResponse
Int -> ReadS ListPolicyGenerationsResponse
ReadS [ListPolicyGenerationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPolicyGenerationsResponse]
$creadListPrec :: ReadPrec [ListPolicyGenerationsResponse]
readPrec :: ReadPrec ListPolicyGenerationsResponse
$creadPrec :: ReadPrec ListPolicyGenerationsResponse
readList :: ReadS [ListPolicyGenerationsResponse]
$creadList :: ReadS [ListPolicyGenerationsResponse]
readsPrec :: Int -> ReadS ListPolicyGenerationsResponse
$creadsPrec :: Int -> ReadS ListPolicyGenerationsResponse
Prelude.Read, Int -> ListPolicyGenerationsResponse -> ShowS
[ListPolicyGenerationsResponse] -> ShowS
ListPolicyGenerationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPolicyGenerationsResponse] -> ShowS
$cshowList :: [ListPolicyGenerationsResponse] -> ShowS
show :: ListPolicyGenerationsResponse -> String
$cshow :: ListPolicyGenerationsResponse -> String
showsPrec :: Int -> ListPolicyGenerationsResponse -> ShowS
$cshowsPrec :: Int -> ListPolicyGenerationsResponse -> ShowS
Prelude.Show, forall x.
Rep ListPolicyGenerationsResponse x
-> ListPolicyGenerationsResponse
forall x.
ListPolicyGenerationsResponse
-> Rep ListPolicyGenerationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListPolicyGenerationsResponse x
-> ListPolicyGenerationsResponse
$cfrom :: forall x.
ListPolicyGenerationsResponse
-> Rep ListPolicyGenerationsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListPolicyGenerationsResponse' 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', 'listPolicyGenerationsResponse_nextToken' - A token used for pagination of results returned.
--
-- 'httpStatus', 'listPolicyGenerationsResponse_httpStatus' - The response's http status code.
--
-- 'policyGenerations', 'listPolicyGenerationsResponse_policyGenerations' - A @PolicyGeneration@ object that contains details about the generated
-- policy.
newListPolicyGenerationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListPolicyGenerationsResponse
newListPolicyGenerationsResponse :: Int -> ListPolicyGenerationsResponse
newListPolicyGenerationsResponse Int
pHttpStatus_ =
  ListPolicyGenerationsResponse'
    { $sel:nextToken:ListPolicyGenerationsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListPolicyGenerationsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:policyGenerations:ListPolicyGenerationsResponse' :: [PolicyGeneration]
policyGenerations = forall a. Monoid a => a
Prelude.mempty
    }

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

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

-- | A @PolicyGeneration@ object that contains details about the generated
-- policy.
listPolicyGenerationsResponse_policyGenerations :: Lens.Lens' ListPolicyGenerationsResponse [PolicyGeneration]
listPolicyGenerationsResponse_policyGenerations :: Lens' ListPolicyGenerationsResponse [PolicyGeneration]
listPolicyGenerationsResponse_policyGenerations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPolicyGenerationsResponse' {[PolicyGeneration]
policyGenerations :: [PolicyGeneration]
$sel:policyGenerations:ListPolicyGenerationsResponse' :: ListPolicyGenerationsResponse -> [PolicyGeneration]
policyGenerations} -> [PolicyGeneration]
policyGenerations) (\s :: ListPolicyGenerationsResponse
s@ListPolicyGenerationsResponse' {} [PolicyGeneration]
a -> ListPolicyGenerationsResponse
s {$sel:policyGenerations:ListPolicyGenerationsResponse' :: [PolicyGeneration]
policyGenerations = [PolicyGeneration]
a} :: ListPolicyGenerationsResponse) 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 ListPolicyGenerationsResponse where
  rnf :: ListPolicyGenerationsResponse -> ()
rnf ListPolicyGenerationsResponse' {Int
[PolicyGeneration]
Maybe Text
policyGenerations :: [PolicyGeneration]
httpStatus :: Int
nextToken :: Maybe Text
$sel:policyGenerations:ListPolicyGenerationsResponse' :: ListPolicyGenerationsResponse -> [PolicyGeneration]
$sel:httpStatus:ListPolicyGenerationsResponse' :: ListPolicyGenerationsResponse -> Int
$sel:nextToken:ListPolicyGenerationsResponse' :: ListPolicyGenerationsResponse -> 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 [PolicyGeneration]
policyGenerations