{-# 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.MigrationHubOrchestrator.RetryWorkflowStep
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retry a failed step in a migration workflow.
module Amazonka.MigrationHubOrchestrator.RetryWorkflowStep
  ( -- * Creating a Request
    RetryWorkflowStep (..),
    newRetryWorkflowStep,

    -- * Request Lenses
    retryWorkflowStep_workflowId,
    retryWorkflowStep_stepGroupId,
    retryWorkflowStep_id,

    -- * Destructuring the Response
    RetryWorkflowStepResponse (..),
    newRetryWorkflowStepResponse,

    -- * Response Lenses
    retryWorkflowStepResponse_id,
    retryWorkflowStepResponse_status,
    retryWorkflowStepResponse_stepGroupId,
    retryWorkflowStepResponse_workflowId,
    retryWorkflowStepResponse_httpStatus,
  )
where

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

-- | /See:/ 'newRetryWorkflowStep' smart constructor.
data RetryWorkflowStep = RetryWorkflowStep'
  { -- | The ID of the migration workflow.
    RetryWorkflowStep -> Text
workflowId :: Prelude.Text,
    -- | The ID of the step group.
    RetryWorkflowStep -> Text
stepGroupId :: Prelude.Text,
    -- | The ID of the step.
    RetryWorkflowStep -> Text
id :: Prelude.Text
  }
  deriving (RetryWorkflowStep -> RetryWorkflowStep -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RetryWorkflowStep -> RetryWorkflowStep -> Bool
$c/= :: RetryWorkflowStep -> RetryWorkflowStep -> Bool
== :: RetryWorkflowStep -> RetryWorkflowStep -> Bool
$c== :: RetryWorkflowStep -> RetryWorkflowStep -> Bool
Prelude.Eq, ReadPrec [RetryWorkflowStep]
ReadPrec RetryWorkflowStep
Int -> ReadS RetryWorkflowStep
ReadS [RetryWorkflowStep]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RetryWorkflowStep]
$creadListPrec :: ReadPrec [RetryWorkflowStep]
readPrec :: ReadPrec RetryWorkflowStep
$creadPrec :: ReadPrec RetryWorkflowStep
readList :: ReadS [RetryWorkflowStep]
$creadList :: ReadS [RetryWorkflowStep]
readsPrec :: Int -> ReadS RetryWorkflowStep
$creadsPrec :: Int -> ReadS RetryWorkflowStep
Prelude.Read, Int -> RetryWorkflowStep -> ShowS
[RetryWorkflowStep] -> ShowS
RetryWorkflowStep -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RetryWorkflowStep] -> ShowS
$cshowList :: [RetryWorkflowStep] -> ShowS
show :: RetryWorkflowStep -> String
$cshow :: RetryWorkflowStep -> String
showsPrec :: Int -> RetryWorkflowStep -> ShowS
$cshowsPrec :: Int -> RetryWorkflowStep -> ShowS
Prelude.Show, forall x. Rep RetryWorkflowStep x -> RetryWorkflowStep
forall x. RetryWorkflowStep -> Rep RetryWorkflowStep x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RetryWorkflowStep x -> RetryWorkflowStep
$cfrom :: forall x. RetryWorkflowStep -> Rep RetryWorkflowStep x
Prelude.Generic)

-- |
-- Create a value of 'RetryWorkflowStep' 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:
--
-- 'workflowId', 'retryWorkflowStep_workflowId' - The ID of the migration workflow.
--
-- 'stepGroupId', 'retryWorkflowStep_stepGroupId' - The ID of the step group.
--
-- 'id', 'retryWorkflowStep_id' - The ID of the step.
newRetryWorkflowStep ::
  -- | 'workflowId'
  Prelude.Text ->
  -- | 'stepGroupId'
  Prelude.Text ->
  -- | 'id'
  Prelude.Text ->
  RetryWorkflowStep
newRetryWorkflowStep :: Text -> Text -> Text -> RetryWorkflowStep
newRetryWorkflowStep Text
pWorkflowId_ Text
pStepGroupId_ Text
pId_ =
  RetryWorkflowStep'
    { $sel:workflowId:RetryWorkflowStep' :: Text
workflowId = Text
pWorkflowId_,
      $sel:stepGroupId:RetryWorkflowStep' :: Text
stepGroupId = Text
pStepGroupId_,
      $sel:id:RetryWorkflowStep' :: Text
id = Text
pId_
    }

-- | The ID of the migration workflow.
retryWorkflowStep_workflowId :: Lens.Lens' RetryWorkflowStep Prelude.Text
retryWorkflowStep_workflowId :: Lens' RetryWorkflowStep Text
retryWorkflowStep_workflowId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RetryWorkflowStep' {Text
workflowId :: Text
$sel:workflowId:RetryWorkflowStep' :: RetryWorkflowStep -> Text
workflowId} -> Text
workflowId) (\s :: RetryWorkflowStep
s@RetryWorkflowStep' {} Text
a -> RetryWorkflowStep
s {$sel:workflowId:RetryWorkflowStep' :: Text
workflowId = Text
a} :: RetryWorkflowStep)

-- | The ID of the step group.
retryWorkflowStep_stepGroupId :: Lens.Lens' RetryWorkflowStep Prelude.Text
retryWorkflowStep_stepGroupId :: Lens' RetryWorkflowStep Text
retryWorkflowStep_stepGroupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RetryWorkflowStep' {Text
stepGroupId :: Text
$sel:stepGroupId:RetryWorkflowStep' :: RetryWorkflowStep -> Text
stepGroupId} -> Text
stepGroupId) (\s :: RetryWorkflowStep
s@RetryWorkflowStep' {} Text
a -> RetryWorkflowStep
s {$sel:stepGroupId:RetryWorkflowStep' :: Text
stepGroupId = Text
a} :: RetryWorkflowStep)

-- | The ID of the step.
retryWorkflowStep_id :: Lens.Lens' RetryWorkflowStep Prelude.Text
retryWorkflowStep_id :: Lens' RetryWorkflowStep Text
retryWorkflowStep_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RetryWorkflowStep' {Text
id :: Text
$sel:id:RetryWorkflowStep' :: RetryWorkflowStep -> Text
id} -> Text
id) (\s :: RetryWorkflowStep
s@RetryWorkflowStep' {} Text
a -> RetryWorkflowStep
s {$sel:id:RetryWorkflowStep' :: Text
id = Text
a} :: RetryWorkflowStep)

instance Core.AWSRequest RetryWorkflowStep where
  type
    AWSResponse RetryWorkflowStep =
      RetryWorkflowStepResponse
  request :: (Service -> Service)
-> RetryWorkflowStep -> Request RetryWorkflowStep
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 RetryWorkflowStep
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse RetryWorkflowStep)))
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 StepStatus
-> Maybe Text
-> Maybe Text
-> Int
-> RetryWorkflowStepResponse
RetryWorkflowStepResponse'
            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
"id")
            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
"status")
            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
"stepGroupId")
            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
"workflowId")
            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 RetryWorkflowStep where
  hashWithSalt :: Int -> RetryWorkflowStep -> Int
hashWithSalt Int
_salt RetryWorkflowStep' {Text
id :: Text
stepGroupId :: Text
workflowId :: Text
$sel:id:RetryWorkflowStep' :: RetryWorkflowStep -> Text
$sel:stepGroupId:RetryWorkflowStep' :: RetryWorkflowStep -> Text
$sel:workflowId:RetryWorkflowStep' :: RetryWorkflowStep -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
workflowId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
stepGroupId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

instance Prelude.NFData RetryWorkflowStep where
  rnf :: RetryWorkflowStep -> ()
rnf RetryWorkflowStep' {Text
id :: Text
stepGroupId :: Text
workflowId :: Text
$sel:id:RetryWorkflowStep' :: RetryWorkflowStep -> Text
$sel:stepGroupId:RetryWorkflowStep' :: RetryWorkflowStep -> Text
$sel:workflowId:RetryWorkflowStep' :: RetryWorkflowStep -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
workflowId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
stepGroupId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
id

instance Data.ToHeaders RetryWorkflowStep where
  toHeaders :: RetryWorkflowStep -> 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.ToJSON RetryWorkflowStep where
  toJSON :: RetryWorkflowStep -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

instance Data.ToPath RetryWorkflowStep where
  toPath :: RetryWorkflowStep -> ByteString
toPath RetryWorkflowStep' {Text
id :: Text
stepGroupId :: Text
workflowId :: Text
$sel:id:RetryWorkflowStep' :: RetryWorkflowStep -> Text
$sel:stepGroupId:RetryWorkflowStep' :: RetryWorkflowStep -> Text
$sel:workflowId:RetryWorkflowStep' :: RetryWorkflowStep -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/retryworkflowstep/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
id]

instance Data.ToQuery RetryWorkflowStep where
  toQuery :: RetryWorkflowStep -> QueryString
toQuery RetryWorkflowStep' {Text
id :: Text
stepGroupId :: Text
workflowId :: Text
$sel:id:RetryWorkflowStep' :: RetryWorkflowStep -> Text
$sel:stepGroupId:RetryWorkflowStep' :: RetryWorkflowStep -> Text
$sel:workflowId:RetryWorkflowStep' :: RetryWorkflowStep -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"workflowId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
workflowId,
        ByteString
"stepGroupId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
stepGroupId
      ]

-- | /See:/ 'newRetryWorkflowStepResponse' smart constructor.
data RetryWorkflowStepResponse = RetryWorkflowStepResponse'
  { -- | The ID of the step.
    RetryWorkflowStepResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The status of the step.
    RetryWorkflowStepResponse -> Maybe StepStatus
status :: Prelude.Maybe StepStatus,
    -- | The ID of the step group.
    RetryWorkflowStepResponse -> Maybe Text
stepGroupId :: Prelude.Maybe Prelude.Text,
    -- | The ID of the migration workflow.
    RetryWorkflowStepResponse -> Maybe Text
workflowId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    RetryWorkflowStepResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (RetryWorkflowStepResponse -> RetryWorkflowStepResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RetryWorkflowStepResponse -> RetryWorkflowStepResponse -> Bool
$c/= :: RetryWorkflowStepResponse -> RetryWorkflowStepResponse -> Bool
== :: RetryWorkflowStepResponse -> RetryWorkflowStepResponse -> Bool
$c== :: RetryWorkflowStepResponse -> RetryWorkflowStepResponse -> Bool
Prelude.Eq, ReadPrec [RetryWorkflowStepResponse]
ReadPrec RetryWorkflowStepResponse
Int -> ReadS RetryWorkflowStepResponse
ReadS [RetryWorkflowStepResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RetryWorkflowStepResponse]
$creadListPrec :: ReadPrec [RetryWorkflowStepResponse]
readPrec :: ReadPrec RetryWorkflowStepResponse
$creadPrec :: ReadPrec RetryWorkflowStepResponse
readList :: ReadS [RetryWorkflowStepResponse]
$creadList :: ReadS [RetryWorkflowStepResponse]
readsPrec :: Int -> ReadS RetryWorkflowStepResponse
$creadsPrec :: Int -> ReadS RetryWorkflowStepResponse
Prelude.Read, Int -> RetryWorkflowStepResponse -> ShowS
[RetryWorkflowStepResponse] -> ShowS
RetryWorkflowStepResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RetryWorkflowStepResponse] -> ShowS
$cshowList :: [RetryWorkflowStepResponse] -> ShowS
show :: RetryWorkflowStepResponse -> String
$cshow :: RetryWorkflowStepResponse -> String
showsPrec :: Int -> RetryWorkflowStepResponse -> ShowS
$cshowsPrec :: Int -> RetryWorkflowStepResponse -> ShowS
Prelude.Show, forall x.
Rep RetryWorkflowStepResponse x -> RetryWorkflowStepResponse
forall x.
RetryWorkflowStepResponse -> Rep RetryWorkflowStepResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RetryWorkflowStepResponse x -> RetryWorkflowStepResponse
$cfrom :: forall x.
RetryWorkflowStepResponse -> Rep RetryWorkflowStepResponse x
Prelude.Generic)

-- |
-- Create a value of 'RetryWorkflowStepResponse' 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:
--
-- 'id', 'retryWorkflowStepResponse_id' - The ID of the step.
--
-- 'status', 'retryWorkflowStepResponse_status' - The status of the step.
--
-- 'stepGroupId', 'retryWorkflowStepResponse_stepGroupId' - The ID of the step group.
--
-- 'workflowId', 'retryWorkflowStepResponse_workflowId' - The ID of the migration workflow.
--
-- 'httpStatus', 'retryWorkflowStepResponse_httpStatus' - The response's http status code.
newRetryWorkflowStepResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  RetryWorkflowStepResponse
newRetryWorkflowStepResponse :: Int -> RetryWorkflowStepResponse
newRetryWorkflowStepResponse Int
pHttpStatus_ =
  RetryWorkflowStepResponse'
    { $sel:id:RetryWorkflowStepResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:status:RetryWorkflowStepResponse' :: Maybe StepStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:stepGroupId:RetryWorkflowStepResponse' :: Maybe Text
stepGroupId = forall a. Maybe a
Prelude.Nothing,
      $sel:workflowId:RetryWorkflowStepResponse' :: Maybe Text
workflowId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:RetryWorkflowStepResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ID of the step.
retryWorkflowStepResponse_id :: Lens.Lens' RetryWorkflowStepResponse (Prelude.Maybe Prelude.Text)
retryWorkflowStepResponse_id :: Lens' RetryWorkflowStepResponse (Maybe Text)
retryWorkflowStepResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RetryWorkflowStepResponse' {Maybe Text
id :: Maybe Text
$sel:id:RetryWorkflowStepResponse' :: RetryWorkflowStepResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: RetryWorkflowStepResponse
s@RetryWorkflowStepResponse' {} Maybe Text
a -> RetryWorkflowStepResponse
s {$sel:id:RetryWorkflowStepResponse' :: Maybe Text
id = Maybe Text
a} :: RetryWorkflowStepResponse)

-- | The status of the step.
retryWorkflowStepResponse_status :: Lens.Lens' RetryWorkflowStepResponse (Prelude.Maybe StepStatus)
retryWorkflowStepResponse_status :: Lens' RetryWorkflowStepResponse (Maybe StepStatus)
retryWorkflowStepResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RetryWorkflowStepResponse' {Maybe StepStatus
status :: Maybe StepStatus
$sel:status:RetryWorkflowStepResponse' :: RetryWorkflowStepResponse -> Maybe StepStatus
status} -> Maybe StepStatus
status) (\s :: RetryWorkflowStepResponse
s@RetryWorkflowStepResponse' {} Maybe StepStatus
a -> RetryWorkflowStepResponse
s {$sel:status:RetryWorkflowStepResponse' :: Maybe StepStatus
status = Maybe StepStatus
a} :: RetryWorkflowStepResponse)

-- | The ID of the step group.
retryWorkflowStepResponse_stepGroupId :: Lens.Lens' RetryWorkflowStepResponse (Prelude.Maybe Prelude.Text)
retryWorkflowStepResponse_stepGroupId :: Lens' RetryWorkflowStepResponse (Maybe Text)
retryWorkflowStepResponse_stepGroupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RetryWorkflowStepResponse' {Maybe Text
stepGroupId :: Maybe Text
$sel:stepGroupId:RetryWorkflowStepResponse' :: RetryWorkflowStepResponse -> Maybe Text
stepGroupId} -> Maybe Text
stepGroupId) (\s :: RetryWorkflowStepResponse
s@RetryWorkflowStepResponse' {} Maybe Text
a -> RetryWorkflowStepResponse
s {$sel:stepGroupId:RetryWorkflowStepResponse' :: Maybe Text
stepGroupId = Maybe Text
a} :: RetryWorkflowStepResponse)

-- | The ID of the migration workflow.
retryWorkflowStepResponse_workflowId :: Lens.Lens' RetryWorkflowStepResponse (Prelude.Maybe Prelude.Text)
retryWorkflowStepResponse_workflowId :: Lens' RetryWorkflowStepResponse (Maybe Text)
retryWorkflowStepResponse_workflowId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RetryWorkflowStepResponse' {Maybe Text
workflowId :: Maybe Text
$sel:workflowId:RetryWorkflowStepResponse' :: RetryWorkflowStepResponse -> Maybe Text
workflowId} -> Maybe Text
workflowId) (\s :: RetryWorkflowStepResponse
s@RetryWorkflowStepResponse' {} Maybe Text
a -> RetryWorkflowStepResponse
s {$sel:workflowId:RetryWorkflowStepResponse' :: Maybe Text
workflowId = Maybe Text
a} :: RetryWorkflowStepResponse)

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

instance Prelude.NFData RetryWorkflowStepResponse where
  rnf :: RetryWorkflowStepResponse -> ()
rnf RetryWorkflowStepResponse' {Int
Maybe Text
Maybe StepStatus
httpStatus :: Int
workflowId :: Maybe Text
stepGroupId :: Maybe Text
status :: Maybe StepStatus
id :: Maybe Text
$sel:httpStatus:RetryWorkflowStepResponse' :: RetryWorkflowStepResponse -> Int
$sel:workflowId:RetryWorkflowStepResponse' :: RetryWorkflowStepResponse -> Maybe Text
$sel:stepGroupId:RetryWorkflowStepResponse' :: RetryWorkflowStepResponse -> Maybe Text
$sel:status:RetryWorkflowStepResponse' :: RetryWorkflowStepResponse -> Maybe StepStatus
$sel:id:RetryWorkflowStepResponse' :: RetryWorkflowStepResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe StepStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
stepGroupId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
workflowId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus