{-# 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.ServiceCatalog.ListServiceActions
-- 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 self-service actions.
--
-- This operation returns paginated results.
module Amazonka.ServiceCatalog.ListServiceActions
  ( -- * Creating a Request
    ListServiceActions (..),
    newListServiceActions,

    -- * Request Lenses
    listServiceActions_acceptLanguage,
    listServiceActions_pageSize,
    listServiceActions_pageToken,

    -- * Destructuring the Response
    ListServiceActionsResponse (..),
    newListServiceActionsResponse,

    -- * Response Lenses
    listServiceActionsResponse_nextPageToken,
    listServiceActionsResponse_serviceActionSummaries,
    listServiceActionsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListServiceActions' smart constructor.
data ListServiceActions = ListServiceActions'
  { -- | The language code.
    --
    -- -   @en@ - English (default)
    --
    -- -   @jp@ - Japanese
    --
    -- -   @zh@ - Chinese
    ListServiceActions -> Maybe Text
acceptLanguage :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of items to return with this call.
    ListServiceActions -> Maybe Natural
pageSize :: Prelude.Maybe Prelude.Natural,
    -- | The page token for the next set of results. To retrieve the first set of
    -- results, use null.
    ListServiceActions -> Maybe Text
pageToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListServiceActions -> ListServiceActions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListServiceActions -> ListServiceActions -> Bool
$c/= :: ListServiceActions -> ListServiceActions -> Bool
== :: ListServiceActions -> ListServiceActions -> Bool
$c== :: ListServiceActions -> ListServiceActions -> Bool
Prelude.Eq, ReadPrec [ListServiceActions]
ReadPrec ListServiceActions
Int -> ReadS ListServiceActions
ReadS [ListServiceActions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListServiceActions]
$creadListPrec :: ReadPrec [ListServiceActions]
readPrec :: ReadPrec ListServiceActions
$creadPrec :: ReadPrec ListServiceActions
readList :: ReadS [ListServiceActions]
$creadList :: ReadS [ListServiceActions]
readsPrec :: Int -> ReadS ListServiceActions
$creadsPrec :: Int -> ReadS ListServiceActions
Prelude.Read, Int -> ListServiceActions -> ShowS
[ListServiceActions] -> ShowS
ListServiceActions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListServiceActions] -> ShowS
$cshowList :: [ListServiceActions] -> ShowS
show :: ListServiceActions -> String
$cshow :: ListServiceActions -> String
showsPrec :: Int -> ListServiceActions -> ShowS
$cshowsPrec :: Int -> ListServiceActions -> ShowS
Prelude.Show, forall x. Rep ListServiceActions x -> ListServiceActions
forall x. ListServiceActions -> Rep ListServiceActions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListServiceActions x -> ListServiceActions
$cfrom :: forall x. ListServiceActions -> Rep ListServiceActions x
Prelude.Generic)

-- |
-- Create a value of 'ListServiceActions' 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:
--
-- 'acceptLanguage', 'listServiceActions_acceptLanguage' - The language code.
--
-- -   @en@ - English (default)
--
-- -   @jp@ - Japanese
--
-- -   @zh@ - Chinese
--
-- 'pageSize', 'listServiceActions_pageSize' - The maximum number of items to return with this call.
--
-- 'pageToken', 'listServiceActions_pageToken' - The page token for the next set of results. To retrieve the first set of
-- results, use null.
newListServiceActions ::
  ListServiceActions
newListServiceActions :: ListServiceActions
newListServiceActions =
  ListServiceActions'
    { $sel:acceptLanguage:ListServiceActions' :: Maybe Text
acceptLanguage =
        forall a. Maybe a
Prelude.Nothing,
      $sel:pageSize:ListServiceActions' :: Maybe Natural
pageSize = forall a. Maybe a
Prelude.Nothing,
      $sel:pageToken:ListServiceActions' :: Maybe Text
pageToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The language code.
--
-- -   @en@ - English (default)
--
-- -   @jp@ - Japanese
--
-- -   @zh@ - Chinese
listServiceActions_acceptLanguage :: Lens.Lens' ListServiceActions (Prelude.Maybe Prelude.Text)
listServiceActions_acceptLanguage :: Lens' ListServiceActions (Maybe Text)
listServiceActions_acceptLanguage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListServiceActions' {Maybe Text
acceptLanguage :: Maybe Text
$sel:acceptLanguage:ListServiceActions' :: ListServiceActions -> Maybe Text
acceptLanguage} -> Maybe Text
acceptLanguage) (\s :: ListServiceActions
s@ListServiceActions' {} Maybe Text
a -> ListServiceActions
s {$sel:acceptLanguage:ListServiceActions' :: Maybe Text
acceptLanguage = Maybe Text
a} :: ListServiceActions)

-- | The maximum number of items to return with this call.
listServiceActions_pageSize :: Lens.Lens' ListServiceActions (Prelude.Maybe Prelude.Natural)
listServiceActions_pageSize :: Lens' ListServiceActions (Maybe Natural)
listServiceActions_pageSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListServiceActions' {Maybe Natural
pageSize :: Maybe Natural
$sel:pageSize:ListServiceActions' :: ListServiceActions -> Maybe Natural
pageSize} -> Maybe Natural
pageSize) (\s :: ListServiceActions
s@ListServiceActions' {} Maybe Natural
a -> ListServiceActions
s {$sel:pageSize:ListServiceActions' :: Maybe Natural
pageSize = Maybe Natural
a} :: ListServiceActions)

-- | The page token for the next set of results. To retrieve the first set of
-- results, use null.
listServiceActions_pageToken :: Lens.Lens' ListServiceActions (Prelude.Maybe Prelude.Text)
listServiceActions_pageToken :: Lens' ListServiceActions (Maybe Text)
listServiceActions_pageToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListServiceActions' {Maybe Text
pageToken :: Maybe Text
$sel:pageToken:ListServiceActions' :: ListServiceActions -> Maybe Text
pageToken} -> Maybe Text
pageToken) (\s :: ListServiceActions
s@ListServiceActions' {} Maybe Text
a -> ListServiceActions
s {$sel:pageToken:ListServiceActions' :: Maybe Text
pageToken = Maybe Text
a} :: ListServiceActions)

instance Core.AWSPager ListServiceActions where
  page :: ListServiceActions
-> AWSResponse ListServiceActions -> Maybe ListServiceActions
page ListServiceActions
rq AWSResponse ListServiceActions
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListServiceActions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListServiceActionsResponse (Maybe Text)
listServiceActionsResponse_nextPageToken
            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 ListServiceActions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListServiceActionsResponse (Maybe [ServiceActionSummary])
listServiceActionsResponse_serviceActionSummaries
            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
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListServiceActions
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListServiceActions (Maybe Text)
listServiceActions_pageToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListServiceActions
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListServiceActionsResponse (Maybe Text)
listServiceActionsResponse_nextPageToken
          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 ListServiceActions where
  type
    AWSResponse ListServiceActions =
      ListServiceActionsResponse
  request :: (Service -> Service)
-> ListServiceActions -> Request ListServiceActions
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 ListServiceActions
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListServiceActions)))
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 [ServiceActionSummary]
-> Int
-> ListServiceActionsResponse
ListServiceActionsResponse'
            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
"NextPageToken")
            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
"ServiceActionSummaries"
                            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable ListServiceActions where
  hashWithSalt :: Int -> ListServiceActions -> Int
hashWithSalt Int
_salt ListServiceActions' {Maybe Natural
Maybe Text
pageToken :: Maybe Text
pageSize :: Maybe Natural
acceptLanguage :: Maybe Text
$sel:pageToken:ListServiceActions' :: ListServiceActions -> Maybe Text
$sel:pageSize:ListServiceActions' :: ListServiceActions -> Maybe Natural
$sel:acceptLanguage:ListServiceActions' :: ListServiceActions -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
acceptLanguage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
pageSize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
pageToken

instance Prelude.NFData ListServiceActions where
  rnf :: ListServiceActions -> ()
rnf ListServiceActions' {Maybe Natural
Maybe Text
pageToken :: Maybe Text
pageSize :: Maybe Natural
acceptLanguage :: Maybe Text
$sel:pageToken:ListServiceActions' :: ListServiceActions -> Maybe Text
$sel:pageSize:ListServiceActions' :: ListServiceActions -> Maybe Natural
$sel:acceptLanguage:ListServiceActions' :: ListServiceActions -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
acceptLanguage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
pageSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
pageToken

instance Data.ToHeaders ListServiceActions where
  toHeaders :: ListServiceActions -> 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
"AWS242ServiceCatalogService.ListServiceActions" ::
                          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 ListServiceActions where
  toJSON :: ListServiceActions -> Value
toJSON ListServiceActions' {Maybe Natural
Maybe Text
pageToken :: Maybe Text
pageSize :: Maybe Natural
acceptLanguage :: Maybe Text
$sel:pageToken:ListServiceActions' :: ListServiceActions -> Maybe Text
$sel:pageSize:ListServiceActions' :: ListServiceActions -> Maybe Natural
$sel:acceptLanguage:ListServiceActions' :: ListServiceActions -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AcceptLanguage" 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
acceptLanguage,
            (Key
"PageSize" 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
pageSize,
            (Key
"PageToken" 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
pageToken
          ]
      )

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

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

-- | /See:/ 'newListServiceActionsResponse' smart constructor.
data ListServiceActionsResponse = ListServiceActionsResponse'
  { -- | The page token to use to retrieve the next set of results. If there are
    -- no additional results, this value is null.
    ListServiceActionsResponse -> Maybe Text
nextPageToken :: Prelude.Maybe Prelude.Text,
    -- | An object containing information about the service actions associated
    -- with the provisioning artifact.
    ListServiceActionsResponse -> Maybe [ServiceActionSummary]
serviceActionSummaries :: Prelude.Maybe [ServiceActionSummary],
    -- | The response's http status code.
    ListServiceActionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListServiceActionsResponse -> ListServiceActionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListServiceActionsResponse -> ListServiceActionsResponse -> Bool
$c/= :: ListServiceActionsResponse -> ListServiceActionsResponse -> Bool
== :: ListServiceActionsResponse -> ListServiceActionsResponse -> Bool
$c== :: ListServiceActionsResponse -> ListServiceActionsResponse -> Bool
Prelude.Eq, ReadPrec [ListServiceActionsResponse]
ReadPrec ListServiceActionsResponse
Int -> ReadS ListServiceActionsResponse
ReadS [ListServiceActionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListServiceActionsResponse]
$creadListPrec :: ReadPrec [ListServiceActionsResponse]
readPrec :: ReadPrec ListServiceActionsResponse
$creadPrec :: ReadPrec ListServiceActionsResponse
readList :: ReadS [ListServiceActionsResponse]
$creadList :: ReadS [ListServiceActionsResponse]
readsPrec :: Int -> ReadS ListServiceActionsResponse
$creadsPrec :: Int -> ReadS ListServiceActionsResponse
Prelude.Read, Int -> ListServiceActionsResponse -> ShowS
[ListServiceActionsResponse] -> ShowS
ListServiceActionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListServiceActionsResponse] -> ShowS
$cshowList :: [ListServiceActionsResponse] -> ShowS
show :: ListServiceActionsResponse -> String
$cshow :: ListServiceActionsResponse -> String
showsPrec :: Int -> ListServiceActionsResponse -> ShowS
$cshowsPrec :: Int -> ListServiceActionsResponse -> ShowS
Prelude.Show, forall x.
Rep ListServiceActionsResponse x -> ListServiceActionsResponse
forall x.
ListServiceActionsResponse -> Rep ListServiceActionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListServiceActionsResponse x -> ListServiceActionsResponse
$cfrom :: forall x.
ListServiceActionsResponse -> Rep ListServiceActionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListServiceActionsResponse' 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:
--
-- 'nextPageToken', 'listServiceActionsResponse_nextPageToken' - The page token to use to retrieve the next set of results. If there are
-- no additional results, this value is null.
--
-- 'serviceActionSummaries', 'listServiceActionsResponse_serviceActionSummaries' - An object containing information about the service actions associated
-- with the provisioning artifact.
--
-- 'httpStatus', 'listServiceActionsResponse_httpStatus' - The response's http status code.
newListServiceActionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListServiceActionsResponse
newListServiceActionsResponse :: Int -> ListServiceActionsResponse
newListServiceActionsResponse Int
pHttpStatus_ =
  ListServiceActionsResponse'
    { $sel:nextPageToken:ListServiceActionsResponse' :: Maybe Text
nextPageToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:serviceActionSummaries:ListServiceActionsResponse' :: Maybe [ServiceActionSummary]
serviceActionSummaries = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListServiceActionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The page token to use to retrieve the next set of results. If there are
-- no additional results, this value is null.
listServiceActionsResponse_nextPageToken :: Lens.Lens' ListServiceActionsResponse (Prelude.Maybe Prelude.Text)
listServiceActionsResponse_nextPageToken :: Lens' ListServiceActionsResponse (Maybe Text)
listServiceActionsResponse_nextPageToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListServiceActionsResponse' {Maybe Text
nextPageToken :: Maybe Text
$sel:nextPageToken:ListServiceActionsResponse' :: ListServiceActionsResponse -> Maybe Text
nextPageToken} -> Maybe Text
nextPageToken) (\s :: ListServiceActionsResponse
s@ListServiceActionsResponse' {} Maybe Text
a -> ListServiceActionsResponse
s {$sel:nextPageToken:ListServiceActionsResponse' :: Maybe Text
nextPageToken = Maybe Text
a} :: ListServiceActionsResponse)

-- | An object containing information about the service actions associated
-- with the provisioning artifact.
listServiceActionsResponse_serviceActionSummaries :: Lens.Lens' ListServiceActionsResponse (Prelude.Maybe [ServiceActionSummary])
listServiceActionsResponse_serviceActionSummaries :: Lens' ListServiceActionsResponse (Maybe [ServiceActionSummary])
listServiceActionsResponse_serviceActionSummaries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListServiceActionsResponse' {Maybe [ServiceActionSummary]
serviceActionSummaries :: Maybe [ServiceActionSummary]
$sel:serviceActionSummaries:ListServiceActionsResponse' :: ListServiceActionsResponse -> Maybe [ServiceActionSummary]
serviceActionSummaries} -> Maybe [ServiceActionSummary]
serviceActionSummaries) (\s :: ListServiceActionsResponse
s@ListServiceActionsResponse' {} Maybe [ServiceActionSummary]
a -> ListServiceActionsResponse
s {$sel:serviceActionSummaries:ListServiceActionsResponse' :: Maybe [ServiceActionSummary]
serviceActionSummaries = Maybe [ServiceActionSummary]
a} :: ListServiceActionsResponse) 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 response's http status code.
listServiceActionsResponse_httpStatus :: Lens.Lens' ListServiceActionsResponse Prelude.Int
listServiceActionsResponse_httpStatus :: Lens' ListServiceActionsResponse Int
listServiceActionsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListServiceActionsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListServiceActionsResponse' :: ListServiceActionsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListServiceActionsResponse
s@ListServiceActionsResponse' {} Int
a -> ListServiceActionsResponse
s {$sel:httpStatus:ListServiceActionsResponse' :: Int
httpStatus = Int
a} :: ListServiceActionsResponse)

instance Prelude.NFData ListServiceActionsResponse where
  rnf :: ListServiceActionsResponse -> ()
rnf ListServiceActionsResponse' {Int
Maybe [ServiceActionSummary]
Maybe Text
httpStatus :: Int
serviceActionSummaries :: Maybe [ServiceActionSummary]
nextPageToken :: Maybe Text
$sel:httpStatus:ListServiceActionsResponse' :: ListServiceActionsResponse -> Int
$sel:serviceActionSummaries:ListServiceActionsResponse' :: ListServiceActionsResponse -> Maybe [ServiceActionSummary]
$sel:nextPageToken:ListServiceActionsResponse' :: ListServiceActionsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextPageToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ServiceActionSummary]
serviceActionSummaries
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus