{-# 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.Glue.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)
--
-- Creates a new workflow.
module Amazonka.Glue.CreateWorkflow
  ( -- * Creating a Request
    CreateWorkflow (..),
    newCreateWorkflow,

    -- * Request Lenses
    createWorkflow_defaultRunProperties,
    createWorkflow_description,
    createWorkflow_maxConcurrentRuns,
    createWorkflow_tags,
    createWorkflow_name,

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

    -- * Response Lenses
    createWorkflowResponse_name,
    createWorkflowResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCreateWorkflow' smart constructor.
data CreateWorkflow = CreateWorkflow'
  { -- | A collection of properties to be used as part of each execution of the
    -- workflow.
    CreateWorkflow -> Maybe (HashMap Text Text)
defaultRunProperties :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | A description of the workflow.
    CreateWorkflow -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | You can use this parameter to prevent unwanted multiple updates to data,
    -- to control costs, or in some cases, to prevent exceeding the maximum
    -- number of concurrent runs of any of the component jobs. If you leave
    -- this parameter blank, there is no limit to the number of concurrent
    -- workflow runs.
    CreateWorkflow -> Maybe Int
maxConcurrentRuns :: Prelude.Maybe Prelude.Int,
    -- | The tags to be used with this workflow.
    CreateWorkflow -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The name to be assigned to the workflow. It should be unique within your
    -- account.
    CreateWorkflow -> Text
name :: Prelude.Text
  }
  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:
--
-- 'defaultRunProperties', 'createWorkflow_defaultRunProperties' - A collection of properties to be used as part of each execution of the
-- workflow.
--
-- 'description', 'createWorkflow_description' - A description of the workflow.
--
-- 'maxConcurrentRuns', 'createWorkflow_maxConcurrentRuns' - You can use this parameter to prevent unwanted multiple updates to data,
-- to control costs, or in some cases, to prevent exceeding the maximum
-- number of concurrent runs of any of the component jobs. If you leave
-- this parameter blank, there is no limit to the number of concurrent
-- workflow runs.
--
-- 'tags', 'createWorkflow_tags' - The tags to be used with this workflow.
--
-- 'name', 'createWorkflow_name' - The name to be assigned to the workflow. It should be unique within your
-- account.
newCreateWorkflow ::
  -- | 'name'
  Prelude.Text ->
  CreateWorkflow
newCreateWorkflow :: Text -> CreateWorkflow
newCreateWorkflow Text
pName_ =
  CreateWorkflow'
    { $sel:defaultRunProperties:CreateWorkflow' :: Maybe (HashMap Text Text)
defaultRunProperties =
        forall a. Maybe a
Prelude.Nothing,
      $sel:description:CreateWorkflow' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:maxConcurrentRuns:CreateWorkflow' :: Maybe Int
maxConcurrentRuns = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateWorkflow' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CreateWorkflow' :: Text
name = Text
pName_
    }

-- | A collection of properties to be used as part of each execution of the
-- workflow.
createWorkflow_defaultRunProperties :: Lens.Lens' CreateWorkflow (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createWorkflow_defaultRunProperties :: Lens' CreateWorkflow (Maybe (HashMap Text Text))
createWorkflow_defaultRunProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkflow' {Maybe (HashMap Text Text)
defaultRunProperties :: Maybe (HashMap Text Text)
$sel:defaultRunProperties:CreateWorkflow' :: CreateWorkflow -> Maybe (HashMap Text Text)
defaultRunProperties} -> Maybe (HashMap Text Text)
defaultRunProperties) (\s :: CreateWorkflow
s@CreateWorkflow' {} Maybe (HashMap Text Text)
a -> CreateWorkflow
s {$sel:defaultRunProperties:CreateWorkflow' :: Maybe (HashMap Text Text)
defaultRunProperties = Maybe (HashMap Text Text)
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

-- | A description of 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)

-- | You can use this parameter to prevent unwanted multiple updates to data,
-- to control costs, or in some cases, to prevent exceeding the maximum
-- number of concurrent runs of any of the component jobs. If you leave
-- this parameter blank, there is no limit to the number of concurrent
-- workflow runs.
createWorkflow_maxConcurrentRuns :: Lens.Lens' CreateWorkflow (Prelude.Maybe Prelude.Int)
createWorkflow_maxConcurrentRuns :: Lens' CreateWorkflow (Maybe Int)
createWorkflow_maxConcurrentRuns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkflow' {Maybe Int
maxConcurrentRuns :: Maybe Int
$sel:maxConcurrentRuns:CreateWorkflow' :: CreateWorkflow -> Maybe Int
maxConcurrentRuns} -> Maybe Int
maxConcurrentRuns) (\s :: CreateWorkflow
s@CreateWorkflow' {} Maybe Int
a -> CreateWorkflow
s {$sel:maxConcurrentRuns:CreateWorkflow' :: Maybe Int
maxConcurrentRuns = Maybe Int
a} :: CreateWorkflow)

-- | The tags to be used with this workflow.
createWorkflow_tags :: Lens.Lens' CreateWorkflow (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createWorkflow_tags :: Lens' CreateWorkflow (Maybe (HashMap Text Text))
createWorkflow_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkflow' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateWorkflow' :: CreateWorkflow -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateWorkflow
s@CreateWorkflow' {} Maybe (HashMap Text Text)
a -> CreateWorkflow
s {$sel:tags:CreateWorkflow' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
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

-- | The name to be assigned to the workflow. It should be unique within your
-- account.
createWorkflow_name :: Lens.Lens' CreateWorkflow Prelude.Text
createWorkflow_name :: Lens' CreateWorkflow Text
createWorkflow_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkflow' {Text
name :: Text
$sel:name:CreateWorkflow' :: CreateWorkflow -> Text
name} -> Text
name) (\s :: CreateWorkflow
s@CreateWorkflow' {} Text
a -> CreateWorkflow
s {$sel:name:CreateWorkflow' :: Text
name = Text
a} :: CreateWorkflow)

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 ->
          Maybe Text -> Int -> CreateWorkflowResponse
CreateWorkflowResponse'
            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
"Name")
            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 CreateWorkflow where
  hashWithSalt :: Int -> CreateWorkflow -> Int
hashWithSalt Int
_salt CreateWorkflow' {Maybe Int
Maybe Text
Maybe (HashMap Text Text)
Text
name :: Text
tags :: Maybe (HashMap Text Text)
maxConcurrentRuns :: Maybe Int
description :: Maybe Text
defaultRunProperties :: Maybe (HashMap Text Text)
$sel:name:CreateWorkflow' :: CreateWorkflow -> Text
$sel:tags:CreateWorkflow' :: CreateWorkflow -> Maybe (HashMap Text Text)
$sel:maxConcurrentRuns:CreateWorkflow' :: CreateWorkflow -> Maybe Int
$sel:description:CreateWorkflow' :: CreateWorkflow -> Maybe Text
$sel:defaultRunProperties:CreateWorkflow' :: CreateWorkflow -> Maybe (HashMap Text Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
defaultRunProperties
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxConcurrentRuns
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData CreateWorkflow where
  rnf :: CreateWorkflow -> ()
rnf CreateWorkflow' {Maybe Int
Maybe Text
Maybe (HashMap Text Text)
Text
name :: Text
tags :: Maybe (HashMap Text Text)
maxConcurrentRuns :: Maybe Int
description :: Maybe Text
defaultRunProperties :: Maybe (HashMap Text Text)
$sel:name:CreateWorkflow' :: CreateWorkflow -> Text
$sel:tags:CreateWorkflow' :: CreateWorkflow -> Maybe (HashMap Text Text)
$sel:maxConcurrentRuns:CreateWorkflow' :: CreateWorkflow -> Maybe Int
$sel:description:CreateWorkflow' :: CreateWorkflow -> Maybe Text
$sel:defaultRunProperties:CreateWorkflow' :: CreateWorkflow -> Maybe (HashMap Text Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
defaultRunProperties
      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 Int
maxConcurrentRuns
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

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
"AWSGlue.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' {Maybe Int
Maybe Text
Maybe (HashMap Text Text)
Text
name :: Text
tags :: Maybe (HashMap Text Text)
maxConcurrentRuns :: Maybe Int
description :: Maybe Text
defaultRunProperties :: Maybe (HashMap Text Text)
$sel:name:CreateWorkflow' :: CreateWorkflow -> Text
$sel:tags:CreateWorkflow' :: CreateWorkflow -> Maybe (HashMap Text Text)
$sel:maxConcurrentRuns:CreateWorkflow' :: CreateWorkflow -> Maybe Int
$sel:description:CreateWorkflow' :: CreateWorkflow -> Maybe Text
$sel:defaultRunProperties:CreateWorkflow' :: CreateWorkflow -> Maybe (HashMap Text Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"DefaultRunProperties" 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 (HashMap Text Text)
defaultRunProperties,
            (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
"MaxConcurrentRuns" 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 Int
maxConcurrentRuns,
            (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 (HashMap Text Text)
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)
          ]
      )

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 name of the workflow which was provided as part of the request.
    CreateWorkflowResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateWorkflowResponse -> Int
httpStatus :: Prelude.Int
  }
  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:
--
-- 'name', 'createWorkflowResponse_name' - The name of the workflow which was provided as part of the request.
--
-- 'httpStatus', 'createWorkflowResponse_httpStatus' - The response's http status code.
newCreateWorkflowResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateWorkflowResponse
newCreateWorkflowResponse :: Int -> CreateWorkflowResponse
newCreateWorkflowResponse Int
pHttpStatus_ =
  CreateWorkflowResponse'
    { $sel:name:CreateWorkflowResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateWorkflowResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The name of the workflow which was provided as part of the request.
createWorkflowResponse_name :: Lens.Lens' CreateWorkflowResponse (Prelude.Maybe Prelude.Text)
createWorkflowResponse_name :: Lens' CreateWorkflowResponse (Maybe Text)
createWorkflowResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkflowResponse' {Maybe Text
name :: Maybe Text
$sel:name:CreateWorkflowResponse' :: CreateWorkflowResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: CreateWorkflowResponse
s@CreateWorkflowResponse' {} Maybe Text
a -> CreateWorkflowResponse
s {$sel:name:CreateWorkflowResponse' :: Maybe Text
name = Maybe Text
a} :: CreateWorkflowResponse)

-- | 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)

instance Prelude.NFData CreateWorkflowResponse where
  rnf :: CreateWorkflowResponse -> ()
rnf CreateWorkflowResponse' {Int
Maybe Text
httpStatus :: Int
name :: Maybe Text
$sel:httpStatus:CreateWorkflowResponse' :: CreateWorkflowResponse -> Int
$sel:name:CreateWorkflowResponse' :: CreateWorkflowResponse -> Maybe Text
..} =
    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 Int
httpStatus