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

    -- * Request Lenses
    getTemplateStep_id,
    getTemplateStep_templateId,
    getTemplateStep_stepGroupId,

    -- * Destructuring the Response
    GetTemplateStepResponse (..),
    newGetTemplateStepResponse,

    -- * Response Lenses
    getTemplateStepResponse_creationTime,
    getTemplateStepResponse_description,
    getTemplateStepResponse_id,
    getTemplateStepResponse_name,
    getTemplateStepResponse_next,
    getTemplateStepResponse_outputs,
    getTemplateStepResponse_previous,
    getTemplateStepResponse_stepActionType,
    getTemplateStepResponse_stepAutomationConfiguration,
    getTemplateStepResponse_stepGroupId,
    getTemplateStepResponse_templateId,
    getTemplateStepResponse_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:/ 'newGetTemplateStep' smart constructor.
data GetTemplateStep = GetTemplateStep'
  { -- | The ID of the step.
    GetTemplateStep -> Text
id :: Prelude.Text,
    -- | The ID of the template.
    GetTemplateStep -> Text
templateId :: Prelude.Text,
    -- | The ID of the step group.
    GetTemplateStep -> Text
stepGroupId :: Prelude.Text
  }
  deriving (GetTemplateStep -> GetTemplateStep -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetTemplateStep -> GetTemplateStep -> Bool
$c/= :: GetTemplateStep -> GetTemplateStep -> Bool
== :: GetTemplateStep -> GetTemplateStep -> Bool
$c== :: GetTemplateStep -> GetTemplateStep -> Bool
Prelude.Eq, ReadPrec [GetTemplateStep]
ReadPrec GetTemplateStep
Int -> ReadS GetTemplateStep
ReadS [GetTemplateStep]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetTemplateStep]
$creadListPrec :: ReadPrec [GetTemplateStep]
readPrec :: ReadPrec GetTemplateStep
$creadPrec :: ReadPrec GetTemplateStep
readList :: ReadS [GetTemplateStep]
$creadList :: ReadS [GetTemplateStep]
readsPrec :: Int -> ReadS GetTemplateStep
$creadsPrec :: Int -> ReadS GetTemplateStep
Prelude.Read, Int -> GetTemplateStep -> ShowS
[GetTemplateStep] -> ShowS
GetTemplateStep -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetTemplateStep] -> ShowS
$cshowList :: [GetTemplateStep] -> ShowS
show :: GetTemplateStep -> String
$cshow :: GetTemplateStep -> String
showsPrec :: Int -> GetTemplateStep -> ShowS
$cshowsPrec :: Int -> GetTemplateStep -> ShowS
Prelude.Show, forall x. Rep GetTemplateStep x -> GetTemplateStep
forall x. GetTemplateStep -> Rep GetTemplateStep x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetTemplateStep x -> GetTemplateStep
$cfrom :: forall x. GetTemplateStep -> Rep GetTemplateStep x
Prelude.Generic)

-- |
-- Create a value of 'GetTemplateStep' 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', 'getTemplateStep_id' - The ID of the step.
--
-- 'templateId', 'getTemplateStep_templateId' - The ID of the template.
--
-- 'stepGroupId', 'getTemplateStep_stepGroupId' - The ID of the step group.
newGetTemplateStep ::
  -- | 'id'
  Prelude.Text ->
  -- | 'templateId'
  Prelude.Text ->
  -- | 'stepGroupId'
  Prelude.Text ->
  GetTemplateStep
newGetTemplateStep :: Text -> Text -> Text -> GetTemplateStep
newGetTemplateStep Text
pId_ Text
pTemplateId_ Text
pStepGroupId_ =
  GetTemplateStep'
    { $sel:id:GetTemplateStep' :: Text
id = Text
pId_,
      $sel:templateId:GetTemplateStep' :: Text
templateId = Text
pTemplateId_,
      $sel:stepGroupId:GetTemplateStep' :: Text
stepGroupId = Text
pStepGroupId_
    }

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

-- | The ID of the template.
getTemplateStep_templateId :: Lens.Lens' GetTemplateStep Prelude.Text
getTemplateStep_templateId :: Lens' GetTemplateStep Text
getTemplateStep_templateId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTemplateStep' {Text
templateId :: Text
$sel:templateId:GetTemplateStep' :: GetTemplateStep -> Text
templateId} -> Text
templateId) (\s :: GetTemplateStep
s@GetTemplateStep' {} Text
a -> GetTemplateStep
s {$sel:templateId:GetTemplateStep' :: Text
templateId = Text
a} :: GetTemplateStep)

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

instance Core.AWSRequest GetTemplateStep where
  type
    AWSResponse GetTemplateStep =
      GetTemplateStepResponse
  request :: (Service -> Service) -> GetTemplateStep -> Request GetTemplateStep
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 GetTemplateStep
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetTemplateStep)))
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 Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [StepOutput]
-> Maybe [Text]
-> Maybe StepActionType
-> Maybe StepAutomationConfiguration
-> Maybe Text
-> Maybe Text
-> Int
-> GetTemplateStepResponse
GetTemplateStepResponse'
            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
"creationTime")
            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
"description")
            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
"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
"name")
            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
"next" 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
"outputs" 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
"previous" 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
"stepActionType")
            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
"stepAutomationConfiguration")
            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
"templateId")
            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 GetTemplateStep where
  hashWithSalt :: Int -> GetTemplateStep -> Int
hashWithSalt Int
_salt GetTemplateStep' {Text
stepGroupId :: Text
templateId :: Text
id :: Text
$sel:stepGroupId:GetTemplateStep' :: GetTemplateStep -> Text
$sel:templateId:GetTemplateStep' :: GetTemplateStep -> Text
$sel:id:GetTemplateStep' :: GetTemplateStep -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
templateId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
stepGroupId

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

instance Data.ToHeaders GetTemplateStep where
  toHeaders :: GetTemplateStep -> 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 GetTemplateStep where
  toPath :: GetTemplateStep -> ByteString
toPath GetTemplateStep' {Text
stepGroupId :: Text
templateId :: Text
id :: Text
$sel:stepGroupId:GetTemplateStep' :: GetTemplateStep -> Text
$sel:templateId:GetTemplateStep' :: GetTemplateStep -> Text
$sel:id:GetTemplateStep' :: GetTemplateStep -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/templatestep/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
id]

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

-- | /See:/ 'newGetTemplateStepResponse' smart constructor.
data GetTemplateStepResponse = GetTemplateStepResponse'
  { -- | The time at which the step was created.
    GetTemplateStepResponse -> Maybe Text
creationTime :: Prelude.Maybe Prelude.Text,
    -- | The description of the step.
    GetTemplateStepResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The ID of the step.
    GetTemplateStepResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The name of the step.
    GetTemplateStepResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The next step.
    GetTemplateStepResponse -> Maybe [Text]
next :: Prelude.Maybe [Prelude.Text],
    -- | The outputs of the step.
    GetTemplateStepResponse -> Maybe [StepOutput]
outputs :: Prelude.Maybe [StepOutput],
    -- | The previous step.
    GetTemplateStepResponse -> Maybe [Text]
previous :: Prelude.Maybe [Prelude.Text],
    -- | The action type of the step. You must run and update the status of a
    -- manual step for the workflow to continue after the completion of the
    -- step.
    GetTemplateStepResponse -> Maybe StepActionType
stepActionType :: Prelude.Maybe StepActionType,
    -- | The custom script to run tests on source or target environments.
    GetTemplateStepResponse -> Maybe StepAutomationConfiguration
stepAutomationConfiguration :: Prelude.Maybe StepAutomationConfiguration,
    -- | The ID of the step group.
    GetTemplateStepResponse -> Maybe Text
stepGroupId :: Prelude.Maybe Prelude.Text,
    -- | The ID of the template.
    GetTemplateStepResponse -> Maybe Text
templateId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetTemplateStepResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetTemplateStepResponse -> GetTemplateStepResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetTemplateStepResponse -> GetTemplateStepResponse -> Bool
$c/= :: GetTemplateStepResponse -> GetTemplateStepResponse -> Bool
== :: GetTemplateStepResponse -> GetTemplateStepResponse -> Bool
$c== :: GetTemplateStepResponse -> GetTemplateStepResponse -> Bool
Prelude.Eq, ReadPrec [GetTemplateStepResponse]
ReadPrec GetTemplateStepResponse
Int -> ReadS GetTemplateStepResponse
ReadS [GetTemplateStepResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetTemplateStepResponse]
$creadListPrec :: ReadPrec [GetTemplateStepResponse]
readPrec :: ReadPrec GetTemplateStepResponse
$creadPrec :: ReadPrec GetTemplateStepResponse
readList :: ReadS [GetTemplateStepResponse]
$creadList :: ReadS [GetTemplateStepResponse]
readsPrec :: Int -> ReadS GetTemplateStepResponse
$creadsPrec :: Int -> ReadS GetTemplateStepResponse
Prelude.Read, Int -> GetTemplateStepResponse -> ShowS
[GetTemplateStepResponse] -> ShowS
GetTemplateStepResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetTemplateStepResponse] -> ShowS
$cshowList :: [GetTemplateStepResponse] -> ShowS
show :: GetTemplateStepResponse -> String
$cshow :: GetTemplateStepResponse -> String
showsPrec :: Int -> GetTemplateStepResponse -> ShowS
$cshowsPrec :: Int -> GetTemplateStepResponse -> ShowS
Prelude.Show, forall x. Rep GetTemplateStepResponse x -> GetTemplateStepResponse
forall x. GetTemplateStepResponse -> Rep GetTemplateStepResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetTemplateStepResponse x -> GetTemplateStepResponse
$cfrom :: forall x. GetTemplateStepResponse -> Rep GetTemplateStepResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetTemplateStepResponse' 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:
--
-- 'creationTime', 'getTemplateStepResponse_creationTime' - The time at which the step was created.
--
-- 'description', 'getTemplateStepResponse_description' - The description of the step.
--
-- 'id', 'getTemplateStepResponse_id' - The ID of the step.
--
-- 'name', 'getTemplateStepResponse_name' - The name of the step.
--
-- 'next', 'getTemplateStepResponse_next' - The next step.
--
-- 'outputs', 'getTemplateStepResponse_outputs' - The outputs of the step.
--
-- 'previous', 'getTemplateStepResponse_previous' - The previous step.
--
-- 'stepActionType', 'getTemplateStepResponse_stepActionType' - The action type of the step. You must run and update the status of a
-- manual step for the workflow to continue after the completion of the
-- step.
--
-- 'stepAutomationConfiguration', 'getTemplateStepResponse_stepAutomationConfiguration' - The custom script to run tests on source or target environments.
--
-- 'stepGroupId', 'getTemplateStepResponse_stepGroupId' - The ID of the step group.
--
-- 'templateId', 'getTemplateStepResponse_templateId' - The ID of the template.
--
-- 'httpStatus', 'getTemplateStepResponse_httpStatus' - The response's http status code.
newGetTemplateStepResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetTemplateStepResponse
newGetTemplateStepResponse :: Int -> GetTemplateStepResponse
newGetTemplateStepResponse Int
pHttpStatus_ =
  GetTemplateStepResponse'
    { $sel:creationTime:GetTemplateStepResponse' :: Maybe Text
creationTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:description:GetTemplateStepResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:id:GetTemplateStepResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:name:GetTemplateStepResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:next:GetTemplateStepResponse' :: Maybe [Text]
next = forall a. Maybe a
Prelude.Nothing,
      $sel:outputs:GetTemplateStepResponse' :: Maybe [StepOutput]
outputs = forall a. Maybe a
Prelude.Nothing,
      $sel:previous:GetTemplateStepResponse' :: Maybe [Text]
previous = forall a. Maybe a
Prelude.Nothing,
      $sel:stepActionType:GetTemplateStepResponse' :: Maybe StepActionType
stepActionType = forall a. Maybe a
Prelude.Nothing,
      $sel:stepAutomationConfiguration:GetTemplateStepResponse' :: Maybe StepAutomationConfiguration
stepAutomationConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:stepGroupId:GetTemplateStepResponse' :: Maybe Text
stepGroupId = forall a. Maybe a
Prelude.Nothing,
      $sel:templateId:GetTemplateStepResponse' :: Maybe Text
templateId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetTemplateStepResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The time at which the step was created.
getTemplateStepResponse_creationTime :: Lens.Lens' GetTemplateStepResponse (Prelude.Maybe Prelude.Text)
getTemplateStepResponse_creationTime :: Lens' GetTemplateStepResponse (Maybe Text)
getTemplateStepResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTemplateStepResponse' {Maybe Text
creationTime :: Maybe Text
$sel:creationTime:GetTemplateStepResponse' :: GetTemplateStepResponse -> Maybe Text
creationTime} -> Maybe Text
creationTime) (\s :: GetTemplateStepResponse
s@GetTemplateStepResponse' {} Maybe Text
a -> GetTemplateStepResponse
s {$sel:creationTime:GetTemplateStepResponse' :: Maybe Text
creationTime = Maybe Text
a} :: GetTemplateStepResponse)

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

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

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

-- | The next step.
getTemplateStepResponse_next :: Lens.Lens' GetTemplateStepResponse (Prelude.Maybe [Prelude.Text])
getTemplateStepResponse_next :: Lens' GetTemplateStepResponse (Maybe [Text])
getTemplateStepResponse_next = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTemplateStepResponse' {Maybe [Text]
next :: Maybe [Text]
$sel:next:GetTemplateStepResponse' :: GetTemplateStepResponse -> Maybe [Text]
next} -> Maybe [Text]
next) (\s :: GetTemplateStepResponse
s@GetTemplateStepResponse' {} Maybe [Text]
a -> GetTemplateStepResponse
s {$sel:next:GetTemplateStepResponse' :: Maybe [Text]
next = Maybe [Text]
a} :: GetTemplateStepResponse) 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 outputs of the step.
getTemplateStepResponse_outputs :: Lens.Lens' GetTemplateStepResponse (Prelude.Maybe [StepOutput])
getTemplateStepResponse_outputs :: Lens' GetTemplateStepResponse (Maybe [StepOutput])
getTemplateStepResponse_outputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTemplateStepResponse' {Maybe [StepOutput]
outputs :: Maybe [StepOutput]
$sel:outputs:GetTemplateStepResponse' :: GetTemplateStepResponse -> Maybe [StepOutput]
outputs} -> Maybe [StepOutput]
outputs) (\s :: GetTemplateStepResponse
s@GetTemplateStepResponse' {} Maybe [StepOutput]
a -> GetTemplateStepResponse
s {$sel:outputs:GetTemplateStepResponse' :: Maybe [StepOutput]
outputs = Maybe [StepOutput]
a} :: GetTemplateStepResponse) 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 previous step.
getTemplateStepResponse_previous :: Lens.Lens' GetTemplateStepResponse (Prelude.Maybe [Prelude.Text])
getTemplateStepResponse_previous :: Lens' GetTemplateStepResponse (Maybe [Text])
getTemplateStepResponse_previous = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTemplateStepResponse' {Maybe [Text]
previous :: Maybe [Text]
$sel:previous:GetTemplateStepResponse' :: GetTemplateStepResponse -> Maybe [Text]
previous} -> Maybe [Text]
previous) (\s :: GetTemplateStepResponse
s@GetTemplateStepResponse' {} Maybe [Text]
a -> GetTemplateStepResponse
s {$sel:previous:GetTemplateStepResponse' :: Maybe [Text]
previous = Maybe [Text]
a} :: GetTemplateStepResponse) 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 action type of the step. You must run and update the status of a
-- manual step for the workflow to continue after the completion of the
-- step.
getTemplateStepResponse_stepActionType :: Lens.Lens' GetTemplateStepResponse (Prelude.Maybe StepActionType)
getTemplateStepResponse_stepActionType :: Lens' GetTemplateStepResponse (Maybe StepActionType)
getTemplateStepResponse_stepActionType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTemplateStepResponse' {Maybe StepActionType
stepActionType :: Maybe StepActionType
$sel:stepActionType:GetTemplateStepResponse' :: GetTemplateStepResponse -> Maybe StepActionType
stepActionType} -> Maybe StepActionType
stepActionType) (\s :: GetTemplateStepResponse
s@GetTemplateStepResponse' {} Maybe StepActionType
a -> GetTemplateStepResponse
s {$sel:stepActionType:GetTemplateStepResponse' :: Maybe StepActionType
stepActionType = Maybe StepActionType
a} :: GetTemplateStepResponse)

-- | The custom script to run tests on source or target environments.
getTemplateStepResponse_stepAutomationConfiguration :: Lens.Lens' GetTemplateStepResponse (Prelude.Maybe StepAutomationConfiguration)
getTemplateStepResponse_stepAutomationConfiguration :: Lens' GetTemplateStepResponse (Maybe StepAutomationConfiguration)
getTemplateStepResponse_stepAutomationConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTemplateStepResponse' {Maybe StepAutomationConfiguration
stepAutomationConfiguration :: Maybe StepAutomationConfiguration
$sel:stepAutomationConfiguration:GetTemplateStepResponse' :: GetTemplateStepResponse -> Maybe StepAutomationConfiguration
stepAutomationConfiguration} -> Maybe StepAutomationConfiguration
stepAutomationConfiguration) (\s :: GetTemplateStepResponse
s@GetTemplateStepResponse' {} Maybe StepAutomationConfiguration
a -> GetTemplateStepResponse
s {$sel:stepAutomationConfiguration:GetTemplateStepResponse' :: Maybe StepAutomationConfiguration
stepAutomationConfiguration = Maybe StepAutomationConfiguration
a} :: GetTemplateStepResponse)

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

-- | The ID of the template.
getTemplateStepResponse_templateId :: Lens.Lens' GetTemplateStepResponse (Prelude.Maybe Prelude.Text)
getTemplateStepResponse_templateId :: Lens' GetTemplateStepResponse (Maybe Text)
getTemplateStepResponse_templateId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetTemplateStepResponse' {Maybe Text
templateId :: Maybe Text
$sel:templateId:GetTemplateStepResponse' :: GetTemplateStepResponse -> Maybe Text
templateId} -> Maybe Text
templateId) (\s :: GetTemplateStepResponse
s@GetTemplateStepResponse' {} Maybe Text
a -> GetTemplateStepResponse
s {$sel:templateId:GetTemplateStepResponse' :: Maybe Text
templateId = Maybe Text
a} :: GetTemplateStepResponse)

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

instance Prelude.NFData GetTemplateStepResponse where
  rnf :: GetTemplateStepResponse -> ()
rnf GetTemplateStepResponse' {Int
Maybe [Text]
Maybe [StepOutput]
Maybe Text
Maybe StepActionType
Maybe StepAutomationConfiguration
httpStatus :: Int
templateId :: Maybe Text
stepGroupId :: Maybe Text
stepAutomationConfiguration :: Maybe StepAutomationConfiguration
stepActionType :: Maybe StepActionType
previous :: Maybe [Text]
outputs :: Maybe [StepOutput]
next :: Maybe [Text]
name :: Maybe Text
id :: Maybe Text
description :: Maybe Text
creationTime :: Maybe Text
$sel:httpStatus:GetTemplateStepResponse' :: GetTemplateStepResponse -> Int
$sel:templateId:GetTemplateStepResponse' :: GetTemplateStepResponse -> Maybe Text
$sel:stepGroupId:GetTemplateStepResponse' :: GetTemplateStepResponse -> Maybe Text
$sel:stepAutomationConfiguration:GetTemplateStepResponse' :: GetTemplateStepResponse -> Maybe StepAutomationConfiguration
$sel:stepActionType:GetTemplateStepResponse' :: GetTemplateStepResponse -> Maybe StepActionType
$sel:previous:GetTemplateStepResponse' :: GetTemplateStepResponse -> Maybe [Text]
$sel:outputs:GetTemplateStepResponse' :: GetTemplateStepResponse -> Maybe [StepOutput]
$sel:next:GetTemplateStepResponse' :: GetTemplateStepResponse -> Maybe [Text]
$sel:name:GetTemplateStepResponse' :: GetTemplateStepResponse -> Maybe Text
$sel:id:GetTemplateStepResponse' :: GetTemplateStepResponse -> Maybe Text
$sel:description:GetTemplateStepResponse' :: GetTemplateStepResponse -> Maybe Text
$sel:creationTime:GetTemplateStepResponse' :: GetTemplateStepResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
next
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [StepOutput]
outputs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
previous
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe StepActionType
stepActionType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe StepAutomationConfiguration
stepAutomationConfiguration
      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
templateId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus