{-# 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.Kafka.ListClusterOperations
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns a list of all the operations that have been performed on the
-- specified MSK cluster.
--
-- This operation returns paginated results.
module Amazonka.Kafka.ListClusterOperations
  ( -- * Creating a Request
    ListClusterOperations (..),
    newListClusterOperations,

    -- * Request Lenses
    listClusterOperations_maxResults,
    listClusterOperations_nextToken,
    listClusterOperations_clusterArn,

    -- * Destructuring the Response
    ListClusterOperationsResponse (..),
    newListClusterOperationsResponse,

    -- * Response Lenses
    listClusterOperationsResponse_clusterOperationInfoList,
    listClusterOperationsResponse_nextToken,
    listClusterOperationsResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Kafka.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newListClusterOperations' smart constructor.
data ListClusterOperations = ListClusterOperations'
  { -- | The maximum number of results to return in the response. If there are
    -- more results, the response includes a NextToken parameter.
    ListClusterOperations -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The paginated results marker. When the result of the operation is
    -- truncated, the call returns NextToken in the response. To get the next
    -- batch, provide this token in your next request.
    ListClusterOperations -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) that uniquely identifies the cluster.
    ListClusterOperations -> Text
clusterArn :: Prelude.Text
  }
  deriving (ListClusterOperations -> ListClusterOperations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListClusterOperations -> ListClusterOperations -> Bool
$c/= :: ListClusterOperations -> ListClusterOperations -> Bool
== :: ListClusterOperations -> ListClusterOperations -> Bool
$c== :: ListClusterOperations -> ListClusterOperations -> Bool
Prelude.Eq, ReadPrec [ListClusterOperations]
ReadPrec ListClusterOperations
Int -> ReadS ListClusterOperations
ReadS [ListClusterOperations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListClusterOperations]
$creadListPrec :: ReadPrec [ListClusterOperations]
readPrec :: ReadPrec ListClusterOperations
$creadPrec :: ReadPrec ListClusterOperations
readList :: ReadS [ListClusterOperations]
$creadList :: ReadS [ListClusterOperations]
readsPrec :: Int -> ReadS ListClusterOperations
$creadsPrec :: Int -> ReadS ListClusterOperations
Prelude.Read, Int -> ListClusterOperations -> ShowS
[ListClusterOperations] -> ShowS
ListClusterOperations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListClusterOperations] -> ShowS
$cshowList :: [ListClusterOperations] -> ShowS
show :: ListClusterOperations -> String
$cshow :: ListClusterOperations -> String
showsPrec :: Int -> ListClusterOperations -> ShowS
$cshowsPrec :: Int -> ListClusterOperations -> ShowS
Prelude.Show, forall x. Rep ListClusterOperations x -> ListClusterOperations
forall x. ListClusterOperations -> Rep ListClusterOperations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListClusterOperations x -> ListClusterOperations
$cfrom :: forall x. ListClusterOperations -> Rep ListClusterOperations x
Prelude.Generic)

-- |
-- Create a value of 'ListClusterOperations' 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', 'listClusterOperations_maxResults' - The maximum number of results to return in the response. If there are
-- more results, the response includes a NextToken parameter.
--
-- 'nextToken', 'listClusterOperations_nextToken' - The paginated results marker. When the result of the operation is
-- truncated, the call returns NextToken in the response. To get the next
-- batch, provide this token in your next request.
--
-- 'clusterArn', 'listClusterOperations_clusterArn' - The Amazon Resource Name (ARN) that uniquely identifies the cluster.
newListClusterOperations ::
  -- | 'clusterArn'
  Prelude.Text ->
  ListClusterOperations
newListClusterOperations :: Text -> ListClusterOperations
newListClusterOperations Text
pClusterArn_ =
  ListClusterOperations'
    { $sel:maxResults:ListClusterOperations' :: Maybe Natural
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListClusterOperations' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:clusterArn:ListClusterOperations' :: Text
clusterArn = Text
pClusterArn_
    }

-- | The maximum number of results to return in the response. If there are
-- more results, the response includes a NextToken parameter.
listClusterOperations_maxResults :: Lens.Lens' ListClusterOperations (Prelude.Maybe Prelude.Natural)
listClusterOperations_maxResults :: Lens' ListClusterOperations (Maybe Natural)
listClusterOperations_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListClusterOperations' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListClusterOperations' :: ListClusterOperations -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListClusterOperations
s@ListClusterOperations' {} Maybe Natural
a -> ListClusterOperations
s {$sel:maxResults:ListClusterOperations' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListClusterOperations)

-- | The paginated results marker. When the result of the operation is
-- truncated, the call returns NextToken in the response. To get the next
-- batch, provide this token in your next request.
listClusterOperations_nextToken :: Lens.Lens' ListClusterOperations (Prelude.Maybe Prelude.Text)
listClusterOperations_nextToken :: Lens' ListClusterOperations (Maybe Text)
listClusterOperations_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListClusterOperations' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListClusterOperations' :: ListClusterOperations -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListClusterOperations
s@ListClusterOperations' {} Maybe Text
a -> ListClusterOperations
s {$sel:nextToken:ListClusterOperations' :: Maybe Text
nextToken = Maybe Text
a} :: ListClusterOperations)

-- | The Amazon Resource Name (ARN) that uniquely identifies the cluster.
listClusterOperations_clusterArn :: Lens.Lens' ListClusterOperations Prelude.Text
listClusterOperations_clusterArn :: Lens' ListClusterOperations Text
listClusterOperations_clusterArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListClusterOperations' {Text
clusterArn :: Text
$sel:clusterArn:ListClusterOperations' :: ListClusterOperations -> Text
clusterArn} -> Text
clusterArn) (\s :: ListClusterOperations
s@ListClusterOperations' {} Text
a -> ListClusterOperations
s {$sel:clusterArn:ListClusterOperations' :: Text
clusterArn = Text
a} :: ListClusterOperations)

instance Core.AWSPager ListClusterOperations where
  page :: ListClusterOperations
-> AWSResponse ListClusterOperations -> Maybe ListClusterOperations
page ListClusterOperations
rq AWSResponse ListClusterOperations
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListClusterOperations
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListClusterOperationsResponse (Maybe Text)
listClusterOperationsResponse_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 ListClusterOperations
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListClusterOperationsResponse (Maybe [ClusterOperationInfo])
listClusterOperationsResponse_clusterOperationInfoList
            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.$ ListClusterOperations
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListClusterOperations (Maybe Text)
listClusterOperations_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListClusterOperations
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListClusterOperationsResponse (Maybe Text)
listClusterOperationsResponse_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 ListClusterOperations where
  type
    AWSResponse ListClusterOperations =
      ListClusterOperationsResponse
  request :: (Service -> Service)
-> ListClusterOperations -> Request ListClusterOperations
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 ListClusterOperations
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListClusterOperations)))
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 [ClusterOperationInfo]
-> Maybe Text -> Int -> ListClusterOperationsResponse
ListClusterOperationsResponse'
            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
"clusterOperationInfoList"
                            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 ListClusterOperations where
  hashWithSalt :: Int -> ListClusterOperations -> Int
hashWithSalt Int
_salt ListClusterOperations' {Maybe Natural
Maybe Text
Text
clusterArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:clusterArn:ListClusterOperations' :: ListClusterOperations -> Text
$sel:nextToken:ListClusterOperations' :: ListClusterOperations -> Maybe Text
$sel:maxResults:ListClusterOperations' :: ListClusterOperations -> 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` Text
clusterArn

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

instance Data.ToHeaders ListClusterOperations where
  toHeaders :: ListClusterOperations -> 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 ListClusterOperations where
  toPath :: ListClusterOperations -> ByteString
toPath ListClusterOperations' {Maybe Natural
Maybe Text
Text
clusterArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:clusterArn:ListClusterOperations' :: ListClusterOperations -> Text
$sel:nextToken:ListClusterOperations' :: ListClusterOperations -> Maybe Text
$sel:maxResults:ListClusterOperations' :: ListClusterOperations -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/v1/clusters/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
clusterArn,
        ByteString
"/operations"
      ]

instance Data.ToQuery ListClusterOperations where
  toQuery :: ListClusterOperations -> QueryString
toQuery ListClusterOperations' {Maybe Natural
Maybe Text
Text
clusterArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:clusterArn:ListClusterOperations' :: ListClusterOperations -> Text
$sel:nextToken:ListClusterOperations' :: ListClusterOperations -> Maybe Text
$sel:maxResults:ListClusterOperations' :: ListClusterOperations -> 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
      ]

-- | /See:/ 'newListClusterOperationsResponse' smart constructor.
data ListClusterOperationsResponse = ListClusterOperationsResponse'
  { -- | An array of cluster operation information objects.
    ListClusterOperationsResponse -> Maybe [ClusterOperationInfo]
clusterOperationInfoList :: Prelude.Maybe [ClusterOperationInfo],
    -- | If the response of ListClusterOperations is truncated, it returns a
    -- NextToken in the response. This Nexttoken should be sent in the
    -- subsequent request to ListClusterOperations.
    ListClusterOperationsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListClusterOperationsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListClusterOperationsResponse
-> ListClusterOperationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListClusterOperationsResponse
-> ListClusterOperationsResponse -> Bool
$c/= :: ListClusterOperationsResponse
-> ListClusterOperationsResponse -> Bool
== :: ListClusterOperationsResponse
-> ListClusterOperationsResponse -> Bool
$c== :: ListClusterOperationsResponse
-> ListClusterOperationsResponse -> Bool
Prelude.Eq, ReadPrec [ListClusterOperationsResponse]
ReadPrec ListClusterOperationsResponse
Int -> ReadS ListClusterOperationsResponse
ReadS [ListClusterOperationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListClusterOperationsResponse]
$creadListPrec :: ReadPrec [ListClusterOperationsResponse]
readPrec :: ReadPrec ListClusterOperationsResponse
$creadPrec :: ReadPrec ListClusterOperationsResponse
readList :: ReadS [ListClusterOperationsResponse]
$creadList :: ReadS [ListClusterOperationsResponse]
readsPrec :: Int -> ReadS ListClusterOperationsResponse
$creadsPrec :: Int -> ReadS ListClusterOperationsResponse
Prelude.Read, Int -> ListClusterOperationsResponse -> ShowS
[ListClusterOperationsResponse] -> ShowS
ListClusterOperationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListClusterOperationsResponse] -> ShowS
$cshowList :: [ListClusterOperationsResponse] -> ShowS
show :: ListClusterOperationsResponse -> String
$cshow :: ListClusterOperationsResponse -> String
showsPrec :: Int -> ListClusterOperationsResponse -> ShowS
$cshowsPrec :: Int -> ListClusterOperationsResponse -> ShowS
Prelude.Show, forall x.
Rep ListClusterOperationsResponse x
-> ListClusterOperationsResponse
forall x.
ListClusterOperationsResponse
-> Rep ListClusterOperationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListClusterOperationsResponse x
-> ListClusterOperationsResponse
$cfrom :: forall x.
ListClusterOperationsResponse
-> Rep ListClusterOperationsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListClusterOperationsResponse' 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:
--
-- 'clusterOperationInfoList', 'listClusterOperationsResponse_clusterOperationInfoList' - An array of cluster operation information objects.
--
-- 'nextToken', 'listClusterOperationsResponse_nextToken' - If the response of ListClusterOperations is truncated, it returns a
-- NextToken in the response. This Nexttoken should be sent in the
-- subsequent request to ListClusterOperations.
--
-- 'httpStatus', 'listClusterOperationsResponse_httpStatus' - The response's http status code.
newListClusterOperationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListClusterOperationsResponse
newListClusterOperationsResponse :: Int -> ListClusterOperationsResponse
newListClusterOperationsResponse Int
pHttpStatus_ =
  ListClusterOperationsResponse'
    { $sel:clusterOperationInfoList:ListClusterOperationsResponse' :: Maybe [ClusterOperationInfo]
clusterOperationInfoList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListClusterOperationsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListClusterOperationsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of cluster operation information objects.
listClusterOperationsResponse_clusterOperationInfoList :: Lens.Lens' ListClusterOperationsResponse (Prelude.Maybe [ClusterOperationInfo])
listClusterOperationsResponse_clusterOperationInfoList :: Lens' ListClusterOperationsResponse (Maybe [ClusterOperationInfo])
listClusterOperationsResponse_clusterOperationInfoList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListClusterOperationsResponse' {Maybe [ClusterOperationInfo]
clusterOperationInfoList :: Maybe [ClusterOperationInfo]
$sel:clusterOperationInfoList:ListClusterOperationsResponse' :: ListClusterOperationsResponse -> Maybe [ClusterOperationInfo]
clusterOperationInfoList} -> Maybe [ClusterOperationInfo]
clusterOperationInfoList) (\s :: ListClusterOperationsResponse
s@ListClusterOperationsResponse' {} Maybe [ClusterOperationInfo]
a -> ListClusterOperationsResponse
s {$sel:clusterOperationInfoList:ListClusterOperationsResponse' :: Maybe [ClusterOperationInfo]
clusterOperationInfoList = Maybe [ClusterOperationInfo]
a} :: ListClusterOperationsResponse) 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

-- | If the response of ListClusterOperations is truncated, it returns a
-- NextToken in the response. This Nexttoken should be sent in the
-- subsequent request to ListClusterOperations.
listClusterOperationsResponse_nextToken :: Lens.Lens' ListClusterOperationsResponse (Prelude.Maybe Prelude.Text)
listClusterOperationsResponse_nextToken :: Lens' ListClusterOperationsResponse (Maybe Text)
listClusterOperationsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListClusterOperationsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListClusterOperationsResponse' :: ListClusterOperationsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListClusterOperationsResponse
s@ListClusterOperationsResponse' {} Maybe Text
a -> ListClusterOperationsResponse
s {$sel:nextToken:ListClusterOperationsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListClusterOperationsResponse)

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

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