{-# 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.Transfer.CreateWorkflow
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Allows you to create a workflow with specified steps and step details
-- the workflow invokes after file transfer completes. After creating a
-- workflow, you can associate the workflow created with any transfer
-- servers by specifying the @workflow-details@ field in @CreateServer@ and
-- @UpdateServer@ operations.
module Amazonka.Transfer.CreateWorkflow
  ( -- * Creating a Request
    CreateWorkflow (..),
    newCreateWorkflow,

    -- * Request Lenses
    createWorkflow_description,
    createWorkflow_onExceptionSteps,
    createWorkflow_tags,
    createWorkflow_steps,

    -- * Destructuring the Response
    CreateWorkflowResponse (..),
    newCreateWorkflowResponse,

    -- * Response Lenses
    createWorkflowResponse_httpStatus,
    createWorkflowResponse_workflowId,
  )
where

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

-- | /See:/ 'newCreateWorkflow' smart constructor.
data CreateWorkflow = CreateWorkflow'
  { -- | A textual description for the workflow.
    CreateWorkflow -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Specifies the steps (actions) to take if errors are encountered during
    -- execution of the workflow.
    --
    -- For custom steps, the lambda function needs to send @FAILURE@ to the
    -- call back API to kick off the exception steps. Additionally, if the
    -- lambda does not send @SUCCESS@ before it times out, the exception steps
    -- are executed.
    CreateWorkflow -> Maybe [WorkflowStep]
onExceptionSteps :: Prelude.Maybe [WorkflowStep],
    -- | Key-value pairs that can be used to group and search for workflows. Tags
    -- are metadata attached to workflows for any purpose.
    CreateWorkflow -> Maybe (NonEmpty Tag)
tags :: Prelude.Maybe (Prelude.NonEmpty Tag),
    -- | Specifies the details for the steps that are in the specified workflow.
    --
    -- The @TYPE@ specifies which of the following actions is being taken for
    -- this step.
    --
    -- -   /COPY/: Copy the file to another location.
    --
    -- -   /CUSTOM/: Perform a custom step with an Lambda function target.
    --
    -- -   /DELETE/: Delete the file.
    --
    -- -   /TAG/: Add a tag to the file.
    --
    -- Currently, copying and tagging are supported only on S3.
    --
    -- For file location, you specify either the S3 bucket and key, or the EFS
    -- file system ID and path.
    CreateWorkflow -> [WorkflowStep]
steps :: [WorkflowStep]
  }
  deriving (CreateWorkflow -> CreateWorkflow -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateWorkflow -> CreateWorkflow -> Bool
$c/= :: CreateWorkflow -> CreateWorkflow -> Bool
== :: CreateWorkflow -> CreateWorkflow -> Bool
$c== :: CreateWorkflow -> CreateWorkflow -> Bool
Prelude.Eq, ReadPrec [CreateWorkflow]
ReadPrec CreateWorkflow
Int -> ReadS CreateWorkflow
ReadS [CreateWorkflow]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateWorkflow]
$creadListPrec :: ReadPrec [CreateWorkflow]
readPrec :: ReadPrec CreateWorkflow
$creadPrec :: ReadPrec CreateWorkflow
readList :: ReadS [CreateWorkflow]
$creadList :: ReadS [CreateWorkflow]
readsPrec :: Int -> ReadS CreateWorkflow
$creadsPrec :: Int -> ReadS CreateWorkflow
Prelude.Read, Int -> CreateWorkflow -> ShowS
[CreateWorkflow] -> ShowS
CreateWorkflow -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateWorkflow] -> ShowS
$cshowList :: [CreateWorkflow] -> ShowS
show :: CreateWorkflow -> String
$cshow :: CreateWorkflow -> String
showsPrec :: Int -> CreateWorkflow -> ShowS
$cshowsPrec :: Int -> CreateWorkflow -> ShowS
Prelude.Show, forall x. Rep CreateWorkflow x -> CreateWorkflow
forall x. CreateWorkflow -> Rep CreateWorkflow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateWorkflow x -> CreateWorkflow
$cfrom :: forall x. CreateWorkflow -> Rep CreateWorkflow x
Prelude.Generic)

-- |
-- Create a value of 'CreateWorkflow' 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:
--
-- 'description', 'createWorkflow_description' - A textual description for the workflow.
--
-- 'onExceptionSteps', 'createWorkflow_onExceptionSteps' - Specifies the steps (actions) to take if errors are encountered during
-- execution of the workflow.
--
-- For custom steps, the lambda function needs to send @FAILURE@ to the
-- call back API to kick off the exception steps. Additionally, if the
-- lambda does not send @SUCCESS@ before it times out, the exception steps
-- are executed.
--
-- 'tags', 'createWorkflow_tags' - Key-value pairs that can be used to group and search for workflows. Tags
-- are metadata attached to workflows for any purpose.
--
-- 'steps', 'createWorkflow_steps' - Specifies the details for the steps that are in the specified workflow.
--
-- The @TYPE@ specifies which of the following actions is being taken for
-- this step.
--
-- -   /COPY/: Copy the file to another location.
--
-- -   /CUSTOM/: Perform a custom step with an Lambda function target.
--
-- -   /DELETE/: Delete the file.
--
-- -   /TAG/: Add a tag to the file.
--
-- Currently, copying and tagging are supported only on S3.
--
-- For file location, you specify either the S3 bucket and key, or the EFS
-- file system ID and path.
newCreateWorkflow ::
  CreateWorkflow
newCreateWorkflow :: CreateWorkflow
newCreateWorkflow =
  CreateWorkflow'
    { $sel:description:CreateWorkflow' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:onExceptionSteps:CreateWorkflow' :: Maybe [WorkflowStep]
onExceptionSteps = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateWorkflow' :: Maybe (NonEmpty Tag)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:steps:CreateWorkflow' :: [WorkflowStep]
steps = forall a. Monoid a => a
Prelude.mempty
    }

-- | A textual description for the workflow.
createWorkflow_description :: Lens.Lens' CreateWorkflow (Prelude.Maybe Prelude.Text)
createWorkflow_description :: Lens' CreateWorkflow (Maybe Text)
createWorkflow_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkflow' {Maybe Text
description :: Maybe Text
$sel:description:CreateWorkflow' :: CreateWorkflow -> Maybe Text
description} -> Maybe Text
description) (\s :: CreateWorkflow
s@CreateWorkflow' {} Maybe Text
a -> CreateWorkflow
s {$sel:description:CreateWorkflow' :: Maybe Text
description = Maybe Text
a} :: CreateWorkflow)

-- | Specifies the steps (actions) to take if errors are encountered during
-- execution of the workflow.
--
-- For custom steps, the lambda function needs to send @FAILURE@ to the
-- call back API to kick off the exception steps. Additionally, if the
-- lambda does not send @SUCCESS@ before it times out, the exception steps
-- are executed.
createWorkflow_onExceptionSteps :: Lens.Lens' CreateWorkflow (Prelude.Maybe [WorkflowStep])
createWorkflow_onExceptionSteps :: Lens' CreateWorkflow (Maybe [WorkflowStep])
createWorkflow_onExceptionSteps = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkflow' {Maybe [WorkflowStep]
onExceptionSteps :: Maybe [WorkflowStep]
$sel:onExceptionSteps:CreateWorkflow' :: CreateWorkflow -> Maybe [WorkflowStep]
onExceptionSteps} -> Maybe [WorkflowStep]
onExceptionSteps) (\s :: CreateWorkflow
s@CreateWorkflow' {} Maybe [WorkflowStep]
a -> CreateWorkflow
s {$sel:onExceptionSteps:CreateWorkflow' :: Maybe [WorkflowStep]
onExceptionSteps = Maybe [WorkflowStep]
a} :: CreateWorkflow) 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

-- | Key-value pairs that can be used to group and search for workflows. Tags
-- are metadata attached to workflows for any purpose.
createWorkflow_tags :: Lens.Lens' CreateWorkflow (Prelude.Maybe (Prelude.NonEmpty Tag))
createWorkflow_tags :: Lens' CreateWorkflow (Maybe (NonEmpty Tag))
createWorkflow_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkflow' {Maybe (NonEmpty Tag)
tags :: Maybe (NonEmpty Tag)
$sel:tags:CreateWorkflow' :: CreateWorkflow -> Maybe (NonEmpty Tag)
tags} -> Maybe (NonEmpty Tag)
tags) (\s :: CreateWorkflow
s@CreateWorkflow' {} Maybe (NonEmpty Tag)
a -> CreateWorkflow
s {$sel:tags:CreateWorkflow' :: Maybe (NonEmpty Tag)
tags = Maybe (NonEmpty Tag)
a} :: CreateWorkflow) 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

-- | Specifies the details for the steps that are in the specified workflow.
--
-- The @TYPE@ specifies which of the following actions is being taken for
-- this step.
--
-- -   /COPY/: Copy the file to another location.
--
-- -   /CUSTOM/: Perform a custom step with an Lambda function target.
--
-- -   /DELETE/: Delete the file.
--
-- -   /TAG/: Add a tag to the file.
--
-- Currently, copying and tagging are supported only on S3.
--
-- For file location, you specify either the S3 bucket and key, or the EFS
-- file system ID and path.
createWorkflow_steps :: Lens.Lens' CreateWorkflow [WorkflowStep]
createWorkflow_steps :: Lens' CreateWorkflow [WorkflowStep]
createWorkflow_steps = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkflow' {[WorkflowStep]
steps :: [WorkflowStep]
$sel:steps:CreateWorkflow' :: CreateWorkflow -> [WorkflowStep]
steps} -> [WorkflowStep]
steps) (\s :: CreateWorkflow
s@CreateWorkflow' {} [WorkflowStep]
a -> CreateWorkflow
s {$sel:steps:CreateWorkflow' :: [WorkflowStep]
steps = [WorkflowStep]
a} :: CreateWorkflow) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest CreateWorkflow where
  type
    AWSResponse CreateWorkflow =
      CreateWorkflowResponse
  request :: (Service -> Service) -> CreateWorkflow -> Request CreateWorkflow
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 CreateWorkflow
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateWorkflow)))
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 ->
          Int -> Text -> CreateWorkflowResponse
CreateWorkflowResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"WorkflowId")
      )

instance Prelude.Hashable CreateWorkflow where
  hashWithSalt :: Int -> CreateWorkflow -> Int
hashWithSalt Int
_salt CreateWorkflow' {[WorkflowStep]
Maybe [WorkflowStep]
Maybe (NonEmpty Tag)
Maybe Text
steps :: [WorkflowStep]
tags :: Maybe (NonEmpty Tag)
onExceptionSteps :: Maybe [WorkflowStep]
description :: Maybe Text
$sel:steps:CreateWorkflow' :: CreateWorkflow -> [WorkflowStep]
$sel:tags:CreateWorkflow' :: CreateWorkflow -> Maybe (NonEmpty Tag)
$sel:onExceptionSteps:CreateWorkflow' :: CreateWorkflow -> Maybe [WorkflowStep]
$sel:description:CreateWorkflow' :: CreateWorkflow -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [WorkflowStep]
onExceptionSteps
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Tag)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [WorkflowStep]
steps

instance Prelude.NFData CreateWorkflow where
  rnf :: CreateWorkflow -> ()
rnf CreateWorkflow' {[WorkflowStep]
Maybe [WorkflowStep]
Maybe (NonEmpty Tag)
Maybe Text
steps :: [WorkflowStep]
tags :: Maybe (NonEmpty Tag)
onExceptionSteps :: Maybe [WorkflowStep]
description :: Maybe Text
$sel:steps:CreateWorkflow' :: CreateWorkflow -> [WorkflowStep]
$sel:tags:CreateWorkflow' :: CreateWorkflow -> Maybe (NonEmpty Tag)
$sel:onExceptionSteps:CreateWorkflow' :: CreateWorkflow -> Maybe [WorkflowStep]
$sel:description:CreateWorkflow' :: CreateWorkflow -> Maybe Text
..} =
    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 [WorkflowStep]
onExceptionSteps
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Tag)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [WorkflowStep]
steps

instance Data.ToHeaders CreateWorkflow where
  toHeaders :: CreateWorkflow -> 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
"TransferService.CreateWorkflow" ::
                          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 CreateWorkflow where
  toJSON :: CreateWorkflow -> Value
toJSON CreateWorkflow' {[WorkflowStep]
Maybe [WorkflowStep]
Maybe (NonEmpty Tag)
Maybe Text
steps :: [WorkflowStep]
tags :: Maybe (NonEmpty Tag)
onExceptionSteps :: Maybe [WorkflowStep]
description :: Maybe Text
$sel:steps:CreateWorkflow' :: CreateWorkflow -> [WorkflowStep]
$sel:tags:CreateWorkflow' :: CreateWorkflow -> Maybe (NonEmpty Tag)
$sel:onExceptionSteps:CreateWorkflow' :: CreateWorkflow -> Maybe [WorkflowStep]
$sel:description:CreateWorkflow' :: CreateWorkflow -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Description" 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
description,
            (Key
"OnExceptionSteps" 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 [WorkflowStep]
onExceptionSteps,
            (Key
"Tags" 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 (NonEmpty Tag)
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"Steps" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [WorkflowStep]
steps)
          ]
      )

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

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

-- | /See:/ 'newCreateWorkflowResponse' smart constructor.
data CreateWorkflowResponse = CreateWorkflowResponse'
  { -- | The response's http status code.
    CreateWorkflowResponse -> Int
httpStatus :: Prelude.Int,
    -- | A unique identifier for the workflow.
    CreateWorkflowResponse -> Text
workflowId :: Prelude.Text
  }
  deriving (CreateWorkflowResponse -> CreateWorkflowResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateWorkflowResponse -> CreateWorkflowResponse -> Bool
$c/= :: CreateWorkflowResponse -> CreateWorkflowResponse -> Bool
== :: CreateWorkflowResponse -> CreateWorkflowResponse -> Bool
$c== :: CreateWorkflowResponse -> CreateWorkflowResponse -> Bool
Prelude.Eq, ReadPrec [CreateWorkflowResponse]
ReadPrec CreateWorkflowResponse
Int -> ReadS CreateWorkflowResponse
ReadS [CreateWorkflowResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateWorkflowResponse]
$creadListPrec :: ReadPrec [CreateWorkflowResponse]
readPrec :: ReadPrec CreateWorkflowResponse
$creadPrec :: ReadPrec CreateWorkflowResponse
readList :: ReadS [CreateWorkflowResponse]
$creadList :: ReadS [CreateWorkflowResponse]
readsPrec :: Int -> ReadS CreateWorkflowResponse
$creadsPrec :: Int -> ReadS CreateWorkflowResponse
Prelude.Read, Int -> CreateWorkflowResponse -> ShowS
[CreateWorkflowResponse] -> ShowS
CreateWorkflowResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateWorkflowResponse] -> ShowS
$cshowList :: [CreateWorkflowResponse] -> ShowS
show :: CreateWorkflowResponse -> String
$cshow :: CreateWorkflowResponse -> String
showsPrec :: Int -> CreateWorkflowResponse -> ShowS
$cshowsPrec :: Int -> CreateWorkflowResponse -> ShowS
Prelude.Show, forall x. Rep CreateWorkflowResponse x -> CreateWorkflowResponse
forall x. CreateWorkflowResponse -> Rep CreateWorkflowResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateWorkflowResponse x -> CreateWorkflowResponse
$cfrom :: forall x. CreateWorkflowResponse -> Rep CreateWorkflowResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateWorkflowResponse' 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:
--
-- 'httpStatus', 'createWorkflowResponse_httpStatus' - The response's http status code.
--
-- 'workflowId', 'createWorkflowResponse_workflowId' - A unique identifier for the workflow.
newCreateWorkflowResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'workflowId'
  Prelude.Text ->
  CreateWorkflowResponse
newCreateWorkflowResponse :: Int -> Text -> CreateWorkflowResponse
newCreateWorkflowResponse Int
pHttpStatus_ Text
pWorkflowId_ =
  CreateWorkflowResponse'
    { $sel:httpStatus:CreateWorkflowResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:workflowId:CreateWorkflowResponse' :: Text
workflowId = Text
pWorkflowId_
    }

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

-- | A unique identifier for the workflow.
createWorkflowResponse_workflowId :: Lens.Lens' CreateWorkflowResponse Prelude.Text
createWorkflowResponse_workflowId :: Lens' CreateWorkflowResponse Text
createWorkflowResponse_workflowId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkflowResponse' {Text
workflowId :: Text
$sel:workflowId:CreateWorkflowResponse' :: CreateWorkflowResponse -> Text
workflowId} -> Text
workflowId) (\s :: CreateWorkflowResponse
s@CreateWorkflowResponse' {} Text
a -> CreateWorkflowResponse
s {$sel:workflowId:CreateWorkflowResponse' :: Text
workflowId = Text
a} :: CreateWorkflowResponse)

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