{-# 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.EMR.ListSteps
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Provides a list of steps for the cluster in reverse order unless you
-- specify @stepIds@ with the request or filter by @StepStates@. You can
-- specify a maximum of 10 @stepIDs@. The CLI automatically paginates
-- results to return a list greater than 50 steps. To return more than 50
-- steps using the CLI, specify a @Marker@, which is a pagination token
-- that indicates the next set of steps to retrieve.
--
-- This operation returns paginated results.
module Amazonka.EMR.ListSteps
  ( -- * Creating a Request
    ListSteps (..),
    newListSteps,

    -- * Request Lenses
    listSteps_marker,
    listSteps_stepIds,
    listSteps_stepStates,
    listSteps_clusterId,

    -- * Destructuring the Response
    ListStepsResponse (..),
    newListStepsResponse,

    -- * Response Lenses
    listStepsResponse_marker,
    listStepsResponse_steps,
    listStepsResponse_httpStatus,
  )
where

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

-- | This input determines which steps to list.
--
-- /See:/ 'newListSteps' smart constructor.
data ListSteps = ListSteps'
  { -- | The maximum number of steps that a single @ListSteps@ action returns is
    -- 50. To return a longer list of steps, use multiple @ListSteps@ actions
    -- along with the @Marker@ parameter, which is a pagination token that
    -- indicates the next set of results to retrieve.
    ListSteps -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The filter to limit the step list based on the identifier of the steps.
    -- You can specify a maximum of ten Step IDs. The character constraint
    -- applies to the overall length of the array.
    ListSteps -> Maybe [Text]
stepIds :: Prelude.Maybe [Prelude.Text],
    -- | The filter to limit the step list based on certain states.
    ListSteps -> Maybe [StepState]
stepStates :: Prelude.Maybe [StepState],
    -- | The identifier of the cluster for which to list the steps.
    ListSteps -> Text
clusterId :: Prelude.Text
  }
  deriving (ListSteps -> ListSteps -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListSteps -> ListSteps -> Bool
$c/= :: ListSteps -> ListSteps -> Bool
== :: ListSteps -> ListSteps -> Bool
$c== :: ListSteps -> ListSteps -> Bool
Prelude.Eq, ReadPrec [ListSteps]
ReadPrec ListSteps
Int -> ReadS ListSteps
ReadS [ListSteps]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListSteps]
$creadListPrec :: ReadPrec [ListSteps]
readPrec :: ReadPrec ListSteps
$creadPrec :: ReadPrec ListSteps
readList :: ReadS [ListSteps]
$creadList :: ReadS [ListSteps]
readsPrec :: Int -> ReadS ListSteps
$creadsPrec :: Int -> ReadS ListSteps
Prelude.Read, Int -> ListSteps -> ShowS
[ListSteps] -> ShowS
ListSteps -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListSteps] -> ShowS
$cshowList :: [ListSteps] -> ShowS
show :: ListSteps -> String
$cshow :: ListSteps -> String
showsPrec :: Int -> ListSteps -> ShowS
$cshowsPrec :: Int -> ListSteps -> ShowS
Prelude.Show, forall x. Rep ListSteps x -> ListSteps
forall x. ListSteps -> Rep ListSteps x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListSteps x -> ListSteps
$cfrom :: forall x. ListSteps -> Rep ListSteps x
Prelude.Generic)

-- |
-- Create a value of 'ListSteps' 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:
--
-- 'marker', 'listSteps_marker' - The maximum number of steps that a single @ListSteps@ action returns is
-- 50. To return a longer list of steps, use multiple @ListSteps@ actions
-- along with the @Marker@ parameter, which is a pagination token that
-- indicates the next set of results to retrieve.
--
-- 'stepIds', 'listSteps_stepIds' - The filter to limit the step list based on the identifier of the steps.
-- You can specify a maximum of ten Step IDs. The character constraint
-- applies to the overall length of the array.
--
-- 'stepStates', 'listSteps_stepStates' - The filter to limit the step list based on certain states.
--
-- 'clusterId', 'listSteps_clusterId' - The identifier of the cluster for which to list the steps.
newListSteps ::
  -- | 'clusterId'
  Prelude.Text ->
  ListSteps
newListSteps :: Text -> ListSteps
newListSteps Text
pClusterId_ =
  ListSteps'
    { $sel:marker:ListSteps' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
      $sel:stepIds:ListSteps' :: Maybe [Text]
stepIds = forall a. Maybe a
Prelude.Nothing,
      $sel:stepStates:ListSteps' :: Maybe [StepState]
stepStates = forall a. Maybe a
Prelude.Nothing,
      $sel:clusterId:ListSteps' :: Text
clusterId = Text
pClusterId_
    }

-- | The maximum number of steps that a single @ListSteps@ action returns is
-- 50. To return a longer list of steps, use multiple @ListSteps@ actions
-- along with the @Marker@ parameter, which is a pagination token that
-- indicates the next set of results to retrieve.
listSteps_marker :: Lens.Lens' ListSteps (Prelude.Maybe Prelude.Text)
listSteps_marker :: Lens' ListSteps (Maybe Text)
listSteps_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSteps' {Maybe Text
marker :: Maybe Text
$sel:marker:ListSteps' :: ListSteps -> Maybe Text
marker} -> Maybe Text
marker) (\s :: ListSteps
s@ListSteps' {} Maybe Text
a -> ListSteps
s {$sel:marker:ListSteps' :: Maybe Text
marker = Maybe Text
a} :: ListSteps)

-- | The filter to limit the step list based on the identifier of the steps.
-- You can specify a maximum of ten Step IDs. The character constraint
-- applies to the overall length of the array.
listSteps_stepIds :: Lens.Lens' ListSteps (Prelude.Maybe [Prelude.Text])
listSteps_stepIds :: Lens' ListSteps (Maybe [Text])
listSteps_stepIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSteps' {Maybe [Text]
stepIds :: Maybe [Text]
$sel:stepIds:ListSteps' :: ListSteps -> Maybe [Text]
stepIds} -> Maybe [Text]
stepIds) (\s :: ListSteps
s@ListSteps' {} Maybe [Text]
a -> ListSteps
s {$sel:stepIds:ListSteps' :: Maybe [Text]
stepIds = Maybe [Text]
a} :: ListSteps) 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 filter to limit the step list based on certain states.
listSteps_stepStates :: Lens.Lens' ListSteps (Prelude.Maybe [StepState])
listSteps_stepStates :: Lens' ListSteps (Maybe [StepState])
listSteps_stepStates = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSteps' {Maybe [StepState]
stepStates :: Maybe [StepState]
$sel:stepStates:ListSteps' :: ListSteps -> Maybe [StepState]
stepStates} -> Maybe [StepState]
stepStates) (\s :: ListSteps
s@ListSteps' {} Maybe [StepState]
a -> ListSteps
s {$sel:stepStates:ListSteps' :: Maybe [StepState]
stepStates = Maybe [StepState]
a} :: ListSteps) 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 identifier of the cluster for which to list the steps.
listSteps_clusterId :: Lens.Lens' ListSteps Prelude.Text
listSteps_clusterId :: Lens' ListSteps Text
listSteps_clusterId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSteps' {Text
clusterId :: Text
$sel:clusterId:ListSteps' :: ListSteps -> Text
clusterId} -> Text
clusterId) (\s :: ListSteps
s@ListSteps' {} Text
a -> ListSteps
s {$sel:clusterId:ListSteps' :: Text
clusterId = Text
a} :: ListSteps)

instance Core.AWSPager ListSteps where
  page :: ListSteps -> AWSResponse ListSteps -> Maybe ListSteps
page ListSteps
rq AWSResponse ListSteps
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListSteps
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListStepsResponse (Maybe Text)
listStepsResponse_marker
            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 ListSteps
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListStepsResponse (Maybe [StepSummary])
listStepsResponse_steps
            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.$ ListSteps
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListSteps (Maybe Text)
listSteps_marker
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListSteps
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListStepsResponse (Maybe Text)
listStepsResponse_marker
          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 ListSteps where
  type AWSResponse ListSteps = ListStepsResponse
  request :: (Service -> Service) -> ListSteps -> Request ListSteps
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 ListSteps
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListSteps)))
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 [StepSummary] -> Int -> ListStepsResponse
ListStepsResponse'
            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
"Marker")
            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
"Steps" 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 ListSteps where
  hashWithSalt :: Int -> ListSteps -> Int
hashWithSalt Int
_salt ListSteps' {Maybe [Text]
Maybe [StepState]
Maybe Text
Text
clusterId :: Text
stepStates :: Maybe [StepState]
stepIds :: Maybe [Text]
marker :: Maybe Text
$sel:clusterId:ListSteps' :: ListSteps -> Text
$sel:stepStates:ListSteps' :: ListSteps -> Maybe [StepState]
$sel:stepIds:ListSteps' :: ListSteps -> Maybe [Text]
$sel:marker:ListSteps' :: ListSteps -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
marker
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
stepIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [StepState]
stepStates
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clusterId

instance Prelude.NFData ListSteps where
  rnf :: ListSteps -> ()
rnf ListSteps' {Maybe [Text]
Maybe [StepState]
Maybe Text
Text
clusterId :: Text
stepStates :: Maybe [StepState]
stepIds :: Maybe [Text]
marker :: Maybe Text
$sel:clusterId:ListSteps' :: ListSteps -> Text
$sel:stepStates:ListSteps' :: ListSteps -> Maybe [StepState]
$sel:stepIds:ListSteps' :: ListSteps -> Maybe [Text]
$sel:marker:ListSteps' :: ListSteps -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
stepIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [StepState]
stepStates
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
clusterId

instance Data.ToHeaders ListSteps where
  toHeaders :: ListSteps -> 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
"ElasticMapReduce.ListSteps" :: 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 ListSteps where
  toJSON :: ListSteps -> Value
toJSON ListSteps' {Maybe [Text]
Maybe [StepState]
Maybe Text
Text
clusterId :: Text
stepStates :: Maybe [StepState]
stepIds :: Maybe [Text]
marker :: Maybe Text
$sel:clusterId:ListSteps' :: ListSteps -> Text
$sel:stepStates:ListSteps' :: ListSteps -> Maybe [StepState]
$sel:stepIds:ListSteps' :: ListSteps -> Maybe [Text]
$sel:marker:ListSteps' :: ListSteps -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Marker" 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
marker,
            (Key
"StepIds" 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]
stepIds,
            (Key
"StepStates" 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 [StepState]
stepStates,
            forall a. a -> Maybe a
Prelude.Just (Key
"ClusterId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
clusterId)
          ]
      )

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

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

-- | This output contains the list of steps returned in reverse order. This
-- means that the last step is the first element in the list.
--
-- /See:/ 'newListStepsResponse' smart constructor.
data ListStepsResponse = ListStepsResponse'
  { -- | The maximum number of steps that a single @ListSteps@ action returns is
    -- 50. To return a longer list of steps, use multiple @ListSteps@ actions
    -- along with the @Marker@ parameter, which is a pagination token that
    -- indicates the next set of results to retrieve.
    ListStepsResponse -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The filtered list of steps for the cluster.
    ListStepsResponse -> Maybe [StepSummary]
steps :: Prelude.Maybe [StepSummary],
    -- | The response's http status code.
    ListStepsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListStepsResponse -> ListStepsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListStepsResponse -> ListStepsResponse -> Bool
$c/= :: ListStepsResponse -> ListStepsResponse -> Bool
== :: ListStepsResponse -> ListStepsResponse -> Bool
$c== :: ListStepsResponse -> ListStepsResponse -> Bool
Prelude.Eq, ReadPrec [ListStepsResponse]
ReadPrec ListStepsResponse
Int -> ReadS ListStepsResponse
ReadS [ListStepsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListStepsResponse]
$creadListPrec :: ReadPrec [ListStepsResponse]
readPrec :: ReadPrec ListStepsResponse
$creadPrec :: ReadPrec ListStepsResponse
readList :: ReadS [ListStepsResponse]
$creadList :: ReadS [ListStepsResponse]
readsPrec :: Int -> ReadS ListStepsResponse
$creadsPrec :: Int -> ReadS ListStepsResponse
Prelude.Read, Int -> ListStepsResponse -> ShowS
[ListStepsResponse] -> ShowS
ListStepsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListStepsResponse] -> ShowS
$cshowList :: [ListStepsResponse] -> ShowS
show :: ListStepsResponse -> String
$cshow :: ListStepsResponse -> String
showsPrec :: Int -> ListStepsResponse -> ShowS
$cshowsPrec :: Int -> ListStepsResponse -> ShowS
Prelude.Show, forall x. Rep ListStepsResponse x -> ListStepsResponse
forall x. ListStepsResponse -> Rep ListStepsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListStepsResponse x -> ListStepsResponse
$cfrom :: forall x. ListStepsResponse -> Rep ListStepsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListStepsResponse' 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:
--
-- 'marker', 'listStepsResponse_marker' - The maximum number of steps that a single @ListSteps@ action returns is
-- 50. To return a longer list of steps, use multiple @ListSteps@ actions
-- along with the @Marker@ parameter, which is a pagination token that
-- indicates the next set of results to retrieve.
--
-- 'steps', 'listStepsResponse_steps' - The filtered list of steps for the cluster.
--
-- 'httpStatus', 'listStepsResponse_httpStatus' - The response's http status code.
newListStepsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListStepsResponse
newListStepsResponse :: Int -> ListStepsResponse
newListStepsResponse Int
pHttpStatus_ =
  ListStepsResponse'
    { $sel:marker:ListStepsResponse' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
      $sel:steps:ListStepsResponse' :: Maybe [StepSummary]
steps = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListStepsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The maximum number of steps that a single @ListSteps@ action returns is
-- 50. To return a longer list of steps, use multiple @ListSteps@ actions
-- along with the @Marker@ parameter, which is a pagination token that
-- indicates the next set of results to retrieve.
listStepsResponse_marker :: Lens.Lens' ListStepsResponse (Prelude.Maybe Prelude.Text)
listStepsResponse_marker :: Lens' ListStepsResponse (Maybe Text)
listStepsResponse_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStepsResponse' {Maybe Text
marker :: Maybe Text
$sel:marker:ListStepsResponse' :: ListStepsResponse -> Maybe Text
marker} -> Maybe Text
marker) (\s :: ListStepsResponse
s@ListStepsResponse' {} Maybe Text
a -> ListStepsResponse
s {$sel:marker:ListStepsResponse' :: Maybe Text
marker = Maybe Text
a} :: ListStepsResponse)

-- | The filtered list of steps for the cluster.
listStepsResponse_steps :: Lens.Lens' ListStepsResponse (Prelude.Maybe [StepSummary])
listStepsResponse_steps :: Lens' ListStepsResponse (Maybe [StepSummary])
listStepsResponse_steps = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStepsResponse' {Maybe [StepSummary]
steps :: Maybe [StepSummary]
$sel:steps:ListStepsResponse' :: ListStepsResponse -> Maybe [StepSummary]
steps} -> Maybe [StepSummary]
steps) (\s :: ListStepsResponse
s@ListStepsResponse' {} Maybe [StepSummary]
a -> ListStepsResponse
s {$sel:steps:ListStepsResponse' :: Maybe [StepSummary]
steps = Maybe [StepSummary]
a} :: ListStepsResponse) 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.
listStepsResponse_httpStatus :: Lens.Lens' ListStepsResponse Prelude.Int
listStepsResponse_httpStatus :: Lens' ListStepsResponse Int
listStepsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStepsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListStepsResponse' :: ListStepsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListStepsResponse
s@ListStepsResponse' {} Int
a -> ListStepsResponse
s {$sel:httpStatus:ListStepsResponse' :: Int
httpStatus = Int
a} :: ListStepsResponse)

instance Prelude.NFData ListStepsResponse where
  rnf :: ListStepsResponse -> ()
rnf ListStepsResponse' {Int
Maybe [StepSummary]
Maybe Text
httpStatus :: Int
steps :: Maybe [StepSummary]
marker :: Maybe Text
$sel:httpStatus:ListStepsResponse' :: ListStepsResponse -> Int
$sel:steps:ListStepsResponse' :: ListStepsResponse -> Maybe [StepSummary]
$sel:marker:ListStepsResponse' :: ListStepsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [StepSummary]
steps
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus