{-# 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.CodePipeline.ListActionTypes
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets a summary of all AWS CodePipeline action types associated with your
-- account.
--
-- This operation returns paginated results.
module Amazonka.CodePipeline.ListActionTypes
  ( -- * Creating a Request
    ListActionTypes (..),
    newListActionTypes,

    -- * Request Lenses
    listActionTypes_actionOwnerFilter,
    listActionTypes_nextToken,
    listActionTypes_regionFilter,

    -- * Destructuring the Response
    ListActionTypesResponse (..),
    newListActionTypesResponse,

    -- * Response Lenses
    listActionTypesResponse_nextToken,
    listActionTypesResponse_httpStatus,
    listActionTypesResponse_actionTypes,
  )
where

import Amazonka.CodePipeline.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

-- | Represents the input of a @ListActionTypes@ action.
--
-- /See:/ 'newListActionTypes' smart constructor.
data ListActionTypes = ListActionTypes'
  { -- | Filters the list of action types to those created by a specified entity.
    ListActionTypes -> Maybe ActionOwner
actionOwnerFilter :: Prelude.Maybe ActionOwner,
    -- | An identifier that was returned from the previous list action types
    -- call, which can be used to return the next set of action types in the
    -- list.
    ListActionTypes -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The Region to filter on for the list of action types.
    ListActionTypes -> Maybe Text
regionFilter :: Prelude.Maybe Prelude.Text
  }
  deriving (ListActionTypes -> ListActionTypes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListActionTypes -> ListActionTypes -> Bool
$c/= :: ListActionTypes -> ListActionTypes -> Bool
== :: ListActionTypes -> ListActionTypes -> Bool
$c== :: ListActionTypes -> ListActionTypes -> Bool
Prelude.Eq, ReadPrec [ListActionTypes]
ReadPrec ListActionTypes
Int -> ReadS ListActionTypes
ReadS [ListActionTypes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListActionTypes]
$creadListPrec :: ReadPrec [ListActionTypes]
readPrec :: ReadPrec ListActionTypes
$creadPrec :: ReadPrec ListActionTypes
readList :: ReadS [ListActionTypes]
$creadList :: ReadS [ListActionTypes]
readsPrec :: Int -> ReadS ListActionTypes
$creadsPrec :: Int -> ReadS ListActionTypes
Prelude.Read, Int -> ListActionTypes -> ShowS
[ListActionTypes] -> ShowS
ListActionTypes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListActionTypes] -> ShowS
$cshowList :: [ListActionTypes] -> ShowS
show :: ListActionTypes -> String
$cshow :: ListActionTypes -> String
showsPrec :: Int -> ListActionTypes -> ShowS
$cshowsPrec :: Int -> ListActionTypes -> ShowS
Prelude.Show, forall x. Rep ListActionTypes x -> ListActionTypes
forall x. ListActionTypes -> Rep ListActionTypes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListActionTypes x -> ListActionTypes
$cfrom :: forall x. ListActionTypes -> Rep ListActionTypes x
Prelude.Generic)

-- |
-- Create a value of 'ListActionTypes' 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:
--
-- 'actionOwnerFilter', 'listActionTypes_actionOwnerFilter' - Filters the list of action types to those created by a specified entity.
--
-- 'nextToken', 'listActionTypes_nextToken' - An identifier that was returned from the previous list action types
-- call, which can be used to return the next set of action types in the
-- list.
--
-- 'regionFilter', 'listActionTypes_regionFilter' - The Region to filter on for the list of action types.
newListActionTypes ::
  ListActionTypes
newListActionTypes :: ListActionTypes
newListActionTypes =
  ListActionTypes'
    { $sel:actionOwnerFilter:ListActionTypes' :: Maybe ActionOwner
actionOwnerFilter =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListActionTypes' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:regionFilter:ListActionTypes' :: Maybe Text
regionFilter = forall a. Maybe a
Prelude.Nothing
    }

-- | Filters the list of action types to those created by a specified entity.
listActionTypes_actionOwnerFilter :: Lens.Lens' ListActionTypes (Prelude.Maybe ActionOwner)
listActionTypes_actionOwnerFilter :: Lens' ListActionTypes (Maybe ActionOwner)
listActionTypes_actionOwnerFilter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListActionTypes' {Maybe ActionOwner
actionOwnerFilter :: Maybe ActionOwner
$sel:actionOwnerFilter:ListActionTypes' :: ListActionTypes -> Maybe ActionOwner
actionOwnerFilter} -> Maybe ActionOwner
actionOwnerFilter) (\s :: ListActionTypes
s@ListActionTypes' {} Maybe ActionOwner
a -> ListActionTypes
s {$sel:actionOwnerFilter:ListActionTypes' :: Maybe ActionOwner
actionOwnerFilter = Maybe ActionOwner
a} :: ListActionTypes)

-- | An identifier that was returned from the previous list action types
-- call, which can be used to return the next set of action types in the
-- list.
listActionTypes_nextToken :: Lens.Lens' ListActionTypes (Prelude.Maybe Prelude.Text)
listActionTypes_nextToken :: Lens' ListActionTypes (Maybe Text)
listActionTypes_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListActionTypes' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListActionTypes' :: ListActionTypes -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListActionTypes
s@ListActionTypes' {} Maybe Text
a -> ListActionTypes
s {$sel:nextToken:ListActionTypes' :: Maybe Text
nextToken = Maybe Text
a} :: ListActionTypes)

-- | The Region to filter on for the list of action types.
listActionTypes_regionFilter :: Lens.Lens' ListActionTypes (Prelude.Maybe Prelude.Text)
listActionTypes_regionFilter :: Lens' ListActionTypes (Maybe Text)
listActionTypes_regionFilter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListActionTypes' {Maybe Text
regionFilter :: Maybe Text
$sel:regionFilter:ListActionTypes' :: ListActionTypes -> Maybe Text
regionFilter} -> Maybe Text
regionFilter) (\s :: ListActionTypes
s@ListActionTypes' {} Maybe Text
a -> ListActionTypes
s {$sel:regionFilter:ListActionTypes' :: Maybe Text
regionFilter = Maybe Text
a} :: ListActionTypes)

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

instance Prelude.Hashable ListActionTypes where
  hashWithSalt :: Int -> ListActionTypes -> Int
hashWithSalt Int
_salt ListActionTypes' {Maybe Text
Maybe ActionOwner
regionFilter :: Maybe Text
nextToken :: Maybe Text
actionOwnerFilter :: Maybe ActionOwner
$sel:regionFilter:ListActionTypes' :: ListActionTypes -> Maybe Text
$sel:nextToken:ListActionTypes' :: ListActionTypes -> Maybe Text
$sel:actionOwnerFilter:ListActionTypes' :: ListActionTypes -> Maybe ActionOwner
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ActionOwner
actionOwnerFilter
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
regionFilter

instance Prelude.NFData ListActionTypes where
  rnf :: ListActionTypes -> ()
rnf ListActionTypes' {Maybe Text
Maybe ActionOwner
regionFilter :: Maybe Text
nextToken :: Maybe Text
actionOwnerFilter :: Maybe ActionOwner
$sel:regionFilter:ListActionTypes' :: ListActionTypes -> Maybe Text
$sel:nextToken:ListActionTypes' :: ListActionTypes -> Maybe Text
$sel:actionOwnerFilter:ListActionTypes' :: ListActionTypes -> Maybe ActionOwner
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ActionOwner
actionOwnerFilter
      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
regionFilter

instance Data.ToHeaders ListActionTypes where
  toHeaders :: ListActionTypes -> 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
"CodePipeline_20150709.ListActionTypes" ::
                          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 ListActionTypes where
  toJSON :: ListActionTypes -> Value
toJSON ListActionTypes' {Maybe Text
Maybe ActionOwner
regionFilter :: Maybe Text
nextToken :: Maybe Text
actionOwnerFilter :: Maybe ActionOwner
$sel:regionFilter:ListActionTypes' :: ListActionTypes -> Maybe Text
$sel:nextToken:ListActionTypes' :: ListActionTypes -> Maybe Text
$sel:actionOwnerFilter:ListActionTypes' :: ListActionTypes -> Maybe ActionOwner
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"actionOwnerFilter" 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 ActionOwner
actionOwnerFilter,
            (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,
            (Key
"regionFilter" 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
regionFilter
          ]
      )

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

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

-- | Represents the output of a @ListActionTypes@ action.
--
-- /See:/ 'newListActionTypesResponse' smart constructor.
data ListActionTypesResponse = ListActionTypesResponse'
  { -- | If the amount of returned information is significantly large, an
    -- identifier is also returned. It can be used in a subsequent list action
    -- types call to return the next set of action types in the list.
    ListActionTypesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListActionTypesResponse -> Int
httpStatus :: Prelude.Int,
    -- | Provides details of the action types.
    ListActionTypesResponse -> [ActionType]
actionTypes :: [ActionType]
  }
  deriving (ListActionTypesResponse -> ListActionTypesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListActionTypesResponse -> ListActionTypesResponse -> Bool
$c/= :: ListActionTypesResponse -> ListActionTypesResponse -> Bool
== :: ListActionTypesResponse -> ListActionTypesResponse -> Bool
$c== :: ListActionTypesResponse -> ListActionTypesResponse -> Bool
Prelude.Eq, ReadPrec [ListActionTypesResponse]
ReadPrec ListActionTypesResponse
Int -> ReadS ListActionTypesResponse
ReadS [ListActionTypesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListActionTypesResponse]
$creadListPrec :: ReadPrec [ListActionTypesResponse]
readPrec :: ReadPrec ListActionTypesResponse
$creadPrec :: ReadPrec ListActionTypesResponse
readList :: ReadS [ListActionTypesResponse]
$creadList :: ReadS [ListActionTypesResponse]
readsPrec :: Int -> ReadS ListActionTypesResponse
$creadsPrec :: Int -> ReadS ListActionTypesResponse
Prelude.Read, Int -> ListActionTypesResponse -> ShowS
[ListActionTypesResponse] -> ShowS
ListActionTypesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListActionTypesResponse] -> ShowS
$cshowList :: [ListActionTypesResponse] -> ShowS
show :: ListActionTypesResponse -> String
$cshow :: ListActionTypesResponse -> String
showsPrec :: Int -> ListActionTypesResponse -> ShowS
$cshowsPrec :: Int -> ListActionTypesResponse -> ShowS
Prelude.Show, forall x. Rep ListActionTypesResponse x -> ListActionTypesResponse
forall x. ListActionTypesResponse -> Rep ListActionTypesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListActionTypesResponse x -> ListActionTypesResponse
$cfrom :: forall x. ListActionTypesResponse -> Rep ListActionTypesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListActionTypesResponse' 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', 'listActionTypesResponse_nextToken' - If the amount of returned information is significantly large, an
-- identifier is also returned. It can be used in a subsequent list action
-- types call to return the next set of action types in the list.
--
-- 'httpStatus', 'listActionTypesResponse_httpStatus' - The response's http status code.
--
-- 'actionTypes', 'listActionTypesResponse_actionTypes' - Provides details of the action types.
newListActionTypesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListActionTypesResponse
newListActionTypesResponse :: Int -> ListActionTypesResponse
newListActionTypesResponse Int
pHttpStatus_ =
  ListActionTypesResponse'
    { $sel:nextToken:ListActionTypesResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListActionTypesResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:actionTypes:ListActionTypesResponse' :: [ActionType]
actionTypes = forall a. Monoid a => a
Prelude.mempty
    }

-- | If the amount of returned information is significantly large, an
-- identifier is also returned. It can be used in a subsequent list action
-- types call to return the next set of action types in the list.
listActionTypesResponse_nextToken :: Lens.Lens' ListActionTypesResponse (Prelude.Maybe Prelude.Text)
listActionTypesResponse_nextToken :: Lens' ListActionTypesResponse (Maybe Text)
listActionTypesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListActionTypesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListActionTypesResponse' :: ListActionTypesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListActionTypesResponse
s@ListActionTypesResponse' {} Maybe Text
a -> ListActionTypesResponse
s {$sel:nextToken:ListActionTypesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListActionTypesResponse)

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

-- | Provides details of the action types.
listActionTypesResponse_actionTypes :: Lens.Lens' ListActionTypesResponse [ActionType]
listActionTypesResponse_actionTypes :: Lens' ListActionTypesResponse [ActionType]
listActionTypesResponse_actionTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListActionTypesResponse' {[ActionType]
actionTypes :: [ActionType]
$sel:actionTypes:ListActionTypesResponse' :: ListActionTypesResponse -> [ActionType]
actionTypes} -> [ActionType]
actionTypes) (\s :: ListActionTypesResponse
s@ListActionTypesResponse' {} [ActionType]
a -> ListActionTypesResponse
s {$sel:actionTypes:ListActionTypesResponse' :: [ActionType]
actionTypes = [ActionType]
a} :: ListActionTypesResponse) 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 ListActionTypesResponse where
  rnf :: ListActionTypesResponse -> ()
rnf ListActionTypesResponse' {Int
[ActionType]
Maybe Text
actionTypes :: [ActionType]
httpStatus :: Int
nextToken :: Maybe Text
$sel:actionTypes:ListActionTypesResponse' :: ListActionTypesResponse -> [ActionType]
$sel:httpStatus:ListActionTypesResponse' :: ListActionTypesResponse -> Int
$sel:nextToken:ListActionTypesResponse' :: ListActionTypesResponse -> 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 [ActionType]
actionTypes