{-# 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.CodeCommit.ListApprovalRuleTemplates
-- 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 approval rule templates in the specified AWS Region in your
-- AWS account. If an AWS Region is not specified, the AWS Region where you
-- are signed in is used.
module Amazonka.CodeCommit.ListApprovalRuleTemplates
  ( -- * Creating a Request
    ListApprovalRuleTemplates (..),
    newListApprovalRuleTemplates,

    -- * Request Lenses
    listApprovalRuleTemplates_maxResults,
    listApprovalRuleTemplates_nextToken,

    -- * Destructuring the Response
    ListApprovalRuleTemplatesResponse (..),
    newListApprovalRuleTemplatesResponse,

    -- * Response Lenses
    listApprovalRuleTemplatesResponse_approvalRuleTemplateNames,
    listApprovalRuleTemplatesResponse_nextToken,
    listApprovalRuleTemplatesResponse_httpStatus,
  )
where

import Amazonka.CodeCommit.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:/ 'newListApprovalRuleTemplates' smart constructor.
data ListApprovalRuleTemplates = ListApprovalRuleTemplates'
  { -- | A non-zero, non-negative integer used to limit the number of returned
    -- results.
    ListApprovalRuleTemplates -> Maybe Int
maxResults :: Prelude.Maybe Prelude.Int,
    -- | An enumeration token that, when provided in a request, returns the next
    -- batch of the results.
    ListApprovalRuleTemplates -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListApprovalRuleTemplates -> ListApprovalRuleTemplates -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListApprovalRuleTemplates -> ListApprovalRuleTemplates -> Bool
$c/= :: ListApprovalRuleTemplates -> ListApprovalRuleTemplates -> Bool
== :: ListApprovalRuleTemplates -> ListApprovalRuleTemplates -> Bool
$c== :: ListApprovalRuleTemplates -> ListApprovalRuleTemplates -> Bool
Prelude.Eq, ReadPrec [ListApprovalRuleTemplates]
ReadPrec ListApprovalRuleTemplates
Int -> ReadS ListApprovalRuleTemplates
ReadS [ListApprovalRuleTemplates]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListApprovalRuleTemplates]
$creadListPrec :: ReadPrec [ListApprovalRuleTemplates]
readPrec :: ReadPrec ListApprovalRuleTemplates
$creadPrec :: ReadPrec ListApprovalRuleTemplates
readList :: ReadS [ListApprovalRuleTemplates]
$creadList :: ReadS [ListApprovalRuleTemplates]
readsPrec :: Int -> ReadS ListApprovalRuleTemplates
$creadsPrec :: Int -> ReadS ListApprovalRuleTemplates
Prelude.Read, Int -> ListApprovalRuleTemplates -> ShowS
[ListApprovalRuleTemplates] -> ShowS
ListApprovalRuleTemplates -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListApprovalRuleTemplates] -> ShowS
$cshowList :: [ListApprovalRuleTemplates] -> ShowS
show :: ListApprovalRuleTemplates -> String
$cshow :: ListApprovalRuleTemplates -> String
showsPrec :: Int -> ListApprovalRuleTemplates -> ShowS
$cshowsPrec :: Int -> ListApprovalRuleTemplates -> ShowS
Prelude.Show, forall x.
Rep ListApprovalRuleTemplates x -> ListApprovalRuleTemplates
forall x.
ListApprovalRuleTemplates -> Rep ListApprovalRuleTemplates x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListApprovalRuleTemplates x -> ListApprovalRuleTemplates
$cfrom :: forall x.
ListApprovalRuleTemplates -> Rep ListApprovalRuleTemplates x
Prelude.Generic)

-- |
-- Create a value of 'ListApprovalRuleTemplates' 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', 'listApprovalRuleTemplates_maxResults' - A non-zero, non-negative integer used to limit the number of returned
-- results.
--
-- 'nextToken', 'listApprovalRuleTemplates_nextToken' - An enumeration token that, when provided in a request, returns the next
-- batch of the results.
newListApprovalRuleTemplates ::
  ListApprovalRuleTemplates
newListApprovalRuleTemplates :: ListApprovalRuleTemplates
newListApprovalRuleTemplates =
  ListApprovalRuleTemplates'
    { $sel:maxResults:ListApprovalRuleTemplates' :: Maybe Int
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListApprovalRuleTemplates' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | A non-zero, non-negative integer used to limit the number of returned
-- results.
listApprovalRuleTemplates_maxResults :: Lens.Lens' ListApprovalRuleTemplates (Prelude.Maybe Prelude.Int)
listApprovalRuleTemplates_maxResults :: Lens' ListApprovalRuleTemplates (Maybe Int)
listApprovalRuleTemplates_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApprovalRuleTemplates' {Maybe Int
maxResults :: Maybe Int
$sel:maxResults:ListApprovalRuleTemplates' :: ListApprovalRuleTemplates -> Maybe Int
maxResults} -> Maybe Int
maxResults) (\s :: ListApprovalRuleTemplates
s@ListApprovalRuleTemplates' {} Maybe Int
a -> ListApprovalRuleTemplates
s {$sel:maxResults:ListApprovalRuleTemplates' :: Maybe Int
maxResults = Maybe Int
a} :: ListApprovalRuleTemplates)

-- | An enumeration token that, when provided in a request, returns the next
-- batch of the results.
listApprovalRuleTemplates_nextToken :: Lens.Lens' ListApprovalRuleTemplates (Prelude.Maybe Prelude.Text)
listApprovalRuleTemplates_nextToken :: Lens' ListApprovalRuleTemplates (Maybe Text)
listApprovalRuleTemplates_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApprovalRuleTemplates' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListApprovalRuleTemplates' :: ListApprovalRuleTemplates -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListApprovalRuleTemplates
s@ListApprovalRuleTemplates' {} Maybe Text
a -> ListApprovalRuleTemplates
s {$sel:nextToken:ListApprovalRuleTemplates' :: Maybe Text
nextToken = Maybe Text
a} :: ListApprovalRuleTemplates)

instance Core.AWSRequest ListApprovalRuleTemplates where
  type
    AWSResponse ListApprovalRuleTemplates =
      ListApprovalRuleTemplatesResponse
  request :: (Service -> Service)
-> ListApprovalRuleTemplates -> Request ListApprovalRuleTemplates
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 ListApprovalRuleTemplates
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListApprovalRuleTemplates)))
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 Text -> Int -> ListApprovalRuleTemplatesResponse
ListApprovalRuleTemplatesResponse'
            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
"approvalRuleTemplateNames"
                            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 ListApprovalRuleTemplates where
  hashWithSalt :: Int -> ListApprovalRuleTemplates -> Int
hashWithSalt Int
_salt ListApprovalRuleTemplates' {Maybe Int
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
$sel:nextToken:ListApprovalRuleTemplates' :: ListApprovalRuleTemplates -> Maybe Text
$sel:maxResults:ListApprovalRuleTemplates' :: ListApprovalRuleTemplates -> 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

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

instance Data.ToHeaders ListApprovalRuleTemplates where
  toHeaders :: ListApprovalRuleTemplates -> 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
"CodeCommit_20150413.ListApprovalRuleTemplates" ::
                          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 ListApprovalRuleTemplates where
  toJSON :: ListApprovalRuleTemplates -> Value
toJSON ListApprovalRuleTemplates' {Maybe Int
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Int
$sel:nextToken:ListApprovalRuleTemplates' :: ListApprovalRuleTemplates -> Maybe Text
$sel:maxResults:ListApprovalRuleTemplates' :: ListApprovalRuleTemplates -> Maybe Int
..} =
    [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 Int
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 ListApprovalRuleTemplates where
  toPath :: ListApprovalRuleTemplates -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newListApprovalRuleTemplatesResponse' smart constructor.
data ListApprovalRuleTemplatesResponse = ListApprovalRuleTemplatesResponse'
  { -- | The names of all the approval rule templates found in the AWS Region for
    -- your AWS account.
    ListApprovalRuleTemplatesResponse -> Maybe [Text]
approvalRuleTemplateNames :: Prelude.Maybe [Prelude.Text],
    -- | An enumeration token that allows the operation to batch the next results
    -- of the operation.
    ListApprovalRuleTemplatesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListApprovalRuleTemplatesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListApprovalRuleTemplatesResponse
-> ListApprovalRuleTemplatesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListApprovalRuleTemplatesResponse
-> ListApprovalRuleTemplatesResponse -> Bool
$c/= :: ListApprovalRuleTemplatesResponse
-> ListApprovalRuleTemplatesResponse -> Bool
== :: ListApprovalRuleTemplatesResponse
-> ListApprovalRuleTemplatesResponse -> Bool
$c== :: ListApprovalRuleTemplatesResponse
-> ListApprovalRuleTemplatesResponse -> Bool
Prelude.Eq, ReadPrec [ListApprovalRuleTemplatesResponse]
ReadPrec ListApprovalRuleTemplatesResponse
Int -> ReadS ListApprovalRuleTemplatesResponse
ReadS [ListApprovalRuleTemplatesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListApprovalRuleTemplatesResponse]
$creadListPrec :: ReadPrec [ListApprovalRuleTemplatesResponse]
readPrec :: ReadPrec ListApprovalRuleTemplatesResponse
$creadPrec :: ReadPrec ListApprovalRuleTemplatesResponse
readList :: ReadS [ListApprovalRuleTemplatesResponse]
$creadList :: ReadS [ListApprovalRuleTemplatesResponse]
readsPrec :: Int -> ReadS ListApprovalRuleTemplatesResponse
$creadsPrec :: Int -> ReadS ListApprovalRuleTemplatesResponse
Prelude.Read, Int -> ListApprovalRuleTemplatesResponse -> ShowS
[ListApprovalRuleTemplatesResponse] -> ShowS
ListApprovalRuleTemplatesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListApprovalRuleTemplatesResponse] -> ShowS
$cshowList :: [ListApprovalRuleTemplatesResponse] -> ShowS
show :: ListApprovalRuleTemplatesResponse -> String
$cshow :: ListApprovalRuleTemplatesResponse -> String
showsPrec :: Int -> ListApprovalRuleTemplatesResponse -> ShowS
$cshowsPrec :: Int -> ListApprovalRuleTemplatesResponse -> ShowS
Prelude.Show, forall x.
Rep ListApprovalRuleTemplatesResponse x
-> ListApprovalRuleTemplatesResponse
forall x.
ListApprovalRuleTemplatesResponse
-> Rep ListApprovalRuleTemplatesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListApprovalRuleTemplatesResponse x
-> ListApprovalRuleTemplatesResponse
$cfrom :: forall x.
ListApprovalRuleTemplatesResponse
-> Rep ListApprovalRuleTemplatesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListApprovalRuleTemplatesResponse' 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:
--
-- 'approvalRuleTemplateNames', 'listApprovalRuleTemplatesResponse_approvalRuleTemplateNames' - The names of all the approval rule templates found in the AWS Region for
-- your AWS account.
--
-- 'nextToken', 'listApprovalRuleTemplatesResponse_nextToken' - An enumeration token that allows the operation to batch the next results
-- of the operation.
--
-- 'httpStatus', 'listApprovalRuleTemplatesResponse_httpStatus' - The response's http status code.
newListApprovalRuleTemplatesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListApprovalRuleTemplatesResponse
newListApprovalRuleTemplatesResponse :: Int -> ListApprovalRuleTemplatesResponse
newListApprovalRuleTemplatesResponse Int
pHttpStatus_ =
  ListApprovalRuleTemplatesResponse'
    { $sel:approvalRuleTemplateNames:ListApprovalRuleTemplatesResponse' :: Maybe [Text]
approvalRuleTemplateNames =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListApprovalRuleTemplatesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListApprovalRuleTemplatesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The names of all the approval rule templates found in the AWS Region for
-- your AWS account.
listApprovalRuleTemplatesResponse_approvalRuleTemplateNames :: Lens.Lens' ListApprovalRuleTemplatesResponse (Prelude.Maybe [Prelude.Text])
listApprovalRuleTemplatesResponse_approvalRuleTemplateNames :: Lens' ListApprovalRuleTemplatesResponse (Maybe [Text])
listApprovalRuleTemplatesResponse_approvalRuleTemplateNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApprovalRuleTemplatesResponse' {Maybe [Text]
approvalRuleTemplateNames :: Maybe [Text]
$sel:approvalRuleTemplateNames:ListApprovalRuleTemplatesResponse' :: ListApprovalRuleTemplatesResponse -> Maybe [Text]
approvalRuleTemplateNames} -> Maybe [Text]
approvalRuleTemplateNames) (\s :: ListApprovalRuleTemplatesResponse
s@ListApprovalRuleTemplatesResponse' {} Maybe [Text]
a -> ListApprovalRuleTemplatesResponse
s {$sel:approvalRuleTemplateNames:ListApprovalRuleTemplatesResponse' :: Maybe [Text]
approvalRuleTemplateNames = Maybe [Text]
a} :: ListApprovalRuleTemplatesResponse) 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

-- | An enumeration token that allows the operation to batch the next results
-- of the operation.
listApprovalRuleTemplatesResponse_nextToken :: Lens.Lens' ListApprovalRuleTemplatesResponse (Prelude.Maybe Prelude.Text)
listApprovalRuleTemplatesResponse_nextToken :: Lens' ListApprovalRuleTemplatesResponse (Maybe Text)
listApprovalRuleTemplatesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApprovalRuleTemplatesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListApprovalRuleTemplatesResponse' :: ListApprovalRuleTemplatesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListApprovalRuleTemplatesResponse
s@ListApprovalRuleTemplatesResponse' {} Maybe Text
a -> ListApprovalRuleTemplatesResponse
s {$sel:nextToken:ListApprovalRuleTemplatesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListApprovalRuleTemplatesResponse)

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

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