{-# 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.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)
--
-- Create a workflow to orchestrate your migrations.
module Amazonka.MigrationHubOrchestrator.CreateWorkflow
  ( -- * Creating a Request
    CreateWorkflow (..),
    newCreateWorkflow,

    -- * Request Lenses
    createWorkflow_description,
    createWorkflow_stepTargets,
    createWorkflow_tags,
    createWorkflow_name,
    createWorkflow_templateId,
    createWorkflow_applicationConfigurationId,
    createWorkflow_inputParameters,

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

    -- * Response Lenses
    createWorkflowResponse_adsApplicationConfigurationId,
    createWorkflowResponse_arn,
    createWorkflowResponse_creationTime,
    createWorkflowResponse_description,
    createWorkflowResponse_id,
    createWorkflowResponse_name,
    createWorkflowResponse_status,
    createWorkflowResponse_stepTargets,
    createWorkflowResponse_tags,
    createWorkflowResponse_templateId,
    createWorkflowResponse_workflowInputs,
    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.MigrationHubOrchestrator.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'
  { -- | The description of the migration workflow.
    CreateWorkflow -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The servers on which a step will be run.
    CreateWorkflow -> Maybe [Text]
stepTargets :: Prelude.Maybe [Prelude.Text],
    -- | The tags to add on a migration workflow.
    CreateWorkflow -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The name of the migration workflow.
    CreateWorkflow -> Text
name :: Prelude.Text,
    -- | The ID of the template.
    CreateWorkflow -> Text
templateId :: Prelude.Text,
    -- | The configuration ID of the application configured in Application
    -- Discovery Service.
    CreateWorkflow -> Text
applicationConfigurationId :: Prelude.Text,
    -- | The input parameters required to create a migration workflow.
    CreateWorkflow -> Sensitive (HashMap Text StepInput)
inputParameters :: Data.Sensitive (Prelude.HashMap Prelude.Text StepInput)
  }
  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, 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' - The description of the migration workflow.
--
-- 'stepTargets', 'createWorkflow_stepTargets' - The servers on which a step will be run.
--
-- 'tags', 'createWorkflow_tags' - The tags to add on a migration workflow.
--
-- 'name', 'createWorkflow_name' - The name of the migration workflow.
--
-- 'templateId', 'createWorkflow_templateId' - The ID of the template.
--
-- 'applicationConfigurationId', 'createWorkflow_applicationConfigurationId' - The configuration ID of the application configured in Application
-- Discovery Service.
--
-- 'inputParameters', 'createWorkflow_inputParameters' - The input parameters required to create a migration workflow.
newCreateWorkflow ::
  -- | 'name'
  Prelude.Text ->
  -- | 'templateId'
  Prelude.Text ->
  -- | 'applicationConfigurationId'
  Prelude.Text ->
  CreateWorkflow
newCreateWorkflow :: Text -> Text -> Text -> CreateWorkflow
newCreateWorkflow
  Text
pName_
  Text
pTemplateId_
  Text
pApplicationConfigurationId_ =
    CreateWorkflow'
      { $sel:description:CreateWorkflow' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
        $sel:stepTargets:CreateWorkflow' :: Maybe [Text]
stepTargets = 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_,
        $sel:templateId:CreateWorkflow' :: Text
templateId = Text
pTemplateId_,
        $sel:applicationConfigurationId:CreateWorkflow' :: Text
applicationConfigurationId =
          Text
pApplicationConfigurationId_,
        $sel:inputParameters:CreateWorkflow' :: Sensitive (HashMap Text StepInput)
inputParameters = forall a. Monoid a => a
Prelude.mempty
      }

-- | The description of the migration 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)

-- | The servers on which a step will be run.
createWorkflow_stepTargets :: Lens.Lens' CreateWorkflow (Prelude.Maybe [Prelude.Text])
createWorkflow_stepTargets :: Lens' CreateWorkflow (Maybe [Text])
createWorkflow_stepTargets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkflow' {Maybe [Text]
stepTargets :: Maybe [Text]
$sel:stepTargets:CreateWorkflow' :: CreateWorkflow -> Maybe [Text]
stepTargets} -> Maybe [Text]
stepTargets) (\s :: CreateWorkflow
s@CreateWorkflow' {} Maybe [Text]
a -> CreateWorkflow
s {$sel:stepTargets:CreateWorkflow' :: Maybe [Text]
stepTargets = Maybe [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 tags to add on a migration 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 of the migration workflow.
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)

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

-- | The configuration ID of the application configured in Application
-- Discovery Service.
createWorkflow_applicationConfigurationId :: Lens.Lens' CreateWorkflow Prelude.Text
createWorkflow_applicationConfigurationId :: Lens' CreateWorkflow Text
createWorkflow_applicationConfigurationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkflow' {Text
applicationConfigurationId :: Text
$sel:applicationConfigurationId:CreateWorkflow' :: CreateWorkflow -> Text
applicationConfigurationId} -> Text
applicationConfigurationId) (\s :: CreateWorkflow
s@CreateWorkflow' {} Text
a -> CreateWorkflow
s {$sel:applicationConfigurationId:CreateWorkflow' :: Text
applicationConfigurationId = Text
a} :: CreateWorkflow)

-- | The input parameters required to create a migration workflow.
createWorkflow_inputParameters :: Lens.Lens' CreateWorkflow (Prelude.HashMap Prelude.Text StepInput)
createWorkflow_inputParameters :: Lens' CreateWorkflow (HashMap Text StepInput)
createWorkflow_inputParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkflow' {Sensitive (HashMap Text StepInput)
inputParameters :: Sensitive (HashMap Text StepInput)
$sel:inputParameters:CreateWorkflow' :: CreateWorkflow -> Sensitive (HashMap Text StepInput)
inputParameters} -> Sensitive (HashMap Text StepInput)
inputParameters) (\s :: CreateWorkflow
s@CreateWorkflow' {} Sensitive (HashMap Text StepInput)
a -> CreateWorkflow
s {$sel:inputParameters:CreateWorkflow' :: Sensitive (HashMap Text StepInput)
inputParameters = Sensitive (HashMap Text StepInput)
a} :: CreateWorkflow) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive 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 ->
          Maybe Text
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe MigrationWorkflowStatusEnum
-> Maybe [Text]
-> Maybe (HashMap Text Text)
-> Maybe Text
-> Maybe (Sensitive (HashMap Text StepInput))
-> 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
"adsApplicationConfigurationId")
            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
"arn")
            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
"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
"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
"stepTargets" 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
"tags" 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
"templateId")
            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
"workflowInputs" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable CreateWorkflow where
  hashWithSalt :: Int -> CreateWorkflow -> Int
hashWithSalt Int
_salt CreateWorkflow' {Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
Text
Sensitive (HashMap Text StepInput)
inputParameters :: Sensitive (HashMap Text StepInput)
applicationConfigurationId :: Text
templateId :: Text
name :: Text
tags :: Maybe (HashMap Text Text)
stepTargets :: Maybe [Text]
description :: Maybe Text
$sel:inputParameters:CreateWorkflow' :: CreateWorkflow -> Sensitive (HashMap Text StepInput)
$sel:applicationConfigurationId:CreateWorkflow' :: CreateWorkflow -> Text
$sel:templateId:CreateWorkflow' :: CreateWorkflow -> Text
$sel:name:CreateWorkflow' :: CreateWorkflow -> Text
$sel:tags:CreateWorkflow' :: CreateWorkflow -> Maybe (HashMap Text Text)
$sel:stepTargets:CreateWorkflow' :: CreateWorkflow -> Maybe [Text]
$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 [Text]
stepTargets
      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
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
templateId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationConfigurationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Sensitive (HashMap Text StepInput)
inputParameters

instance Prelude.NFData CreateWorkflow where
  rnf :: CreateWorkflow -> ()
rnf CreateWorkflow' {Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
Text
Sensitive (HashMap Text StepInput)
inputParameters :: Sensitive (HashMap Text StepInput)
applicationConfigurationId :: Text
templateId :: Text
name :: Text
tags :: Maybe (HashMap Text Text)
stepTargets :: Maybe [Text]
description :: Maybe Text
$sel:inputParameters:CreateWorkflow' :: CreateWorkflow -> Sensitive (HashMap Text StepInput)
$sel:applicationConfigurationId:CreateWorkflow' :: CreateWorkflow -> Text
$sel:templateId:CreateWorkflow' :: CreateWorkflow -> Text
$sel:name:CreateWorkflow' :: CreateWorkflow -> Text
$sel:tags:CreateWorkflow' :: CreateWorkflow -> Maybe (HashMap Text Text)
$sel:stepTargets:CreateWorkflow' :: CreateWorkflow -> Maybe [Text]
$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 [Text]
stepTargets
      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
      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
applicationConfigurationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Sensitive (HashMap Text StepInput)
inputParameters

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
"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 [Text]
Maybe Text
Maybe (HashMap Text Text)
Text
Sensitive (HashMap Text StepInput)
inputParameters :: Sensitive (HashMap Text StepInput)
applicationConfigurationId :: Text
templateId :: Text
name :: Text
tags :: Maybe (HashMap Text Text)
stepTargets :: Maybe [Text]
description :: Maybe Text
$sel:inputParameters:CreateWorkflow' :: CreateWorkflow -> Sensitive (HashMap Text StepInput)
$sel:applicationConfigurationId:CreateWorkflow' :: CreateWorkflow -> Text
$sel:templateId:CreateWorkflow' :: CreateWorkflow -> Text
$sel:name:CreateWorkflow' :: CreateWorkflow -> Text
$sel:tags:CreateWorkflow' :: CreateWorkflow -> Maybe (HashMap Text Text)
$sel:stepTargets:CreateWorkflow' :: CreateWorkflow -> Maybe [Text]
$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
"stepTargets" 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]
stepTargets,
            (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),
            forall a. a -> Maybe a
Prelude.Just (Key
"templateId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
templateId),
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"applicationConfigurationId"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
applicationConfigurationId
              ),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"inputParameters" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Sensitive (HashMap Text StepInput)
inputParameters)
          ]
      )

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

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 configuration ID of the application configured in Application
    -- Discovery Service.
    CreateWorkflowResponse -> Maybe Text
adsApplicationConfigurationId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the migration workflow.
    CreateWorkflowResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The time at which the migration workflow was created.
    CreateWorkflowResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | The description of the migration workflow.
    CreateWorkflowResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The ID of the migration workflow.
    CreateWorkflowResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The name of the migration workflow.
    CreateWorkflowResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The status of the migration workflow.
    CreateWorkflowResponse -> Maybe MigrationWorkflowStatusEnum
status :: Prelude.Maybe MigrationWorkflowStatusEnum,
    -- | The servers on which a step will be run.
    CreateWorkflowResponse -> Maybe [Text]
stepTargets :: Prelude.Maybe [Prelude.Text],
    -- | The tags to add on a migration workflow.
    CreateWorkflowResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The ID of the template.
    CreateWorkflowResponse -> Maybe Text
templateId :: Prelude.Maybe Prelude.Text,
    -- | The inputs for creating a migration workflow.
    CreateWorkflowResponse
-> Maybe (Sensitive (HashMap Text StepInput))
workflowInputs :: Prelude.Maybe (Data.Sensitive (Prelude.HashMap Prelude.Text StepInput)),
    -- | 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, 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:
--
-- 'adsApplicationConfigurationId', 'createWorkflowResponse_adsApplicationConfigurationId' - The configuration ID of the application configured in Application
-- Discovery Service.
--
-- 'arn', 'createWorkflowResponse_arn' - The Amazon Resource Name (ARN) of the migration workflow.
--
-- 'creationTime', 'createWorkflowResponse_creationTime' - The time at which the migration workflow was created.
--
-- 'description', 'createWorkflowResponse_description' - The description of the migration workflow.
--
-- 'id', 'createWorkflowResponse_id' - The ID of the migration workflow.
--
-- 'name', 'createWorkflowResponse_name' - The name of the migration workflow.
--
-- 'status', 'createWorkflowResponse_status' - The status of the migration workflow.
--
-- 'stepTargets', 'createWorkflowResponse_stepTargets' - The servers on which a step will be run.
--
-- 'tags', 'createWorkflowResponse_tags' - The tags to add on a migration workflow.
--
-- 'templateId', 'createWorkflowResponse_templateId' - The ID of the template.
--
-- 'workflowInputs', 'createWorkflowResponse_workflowInputs' - The inputs for creating a migration workflow.
--
-- 'httpStatus', 'createWorkflowResponse_httpStatus' - The response's http status code.
newCreateWorkflowResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateWorkflowResponse
newCreateWorkflowResponse :: Int -> CreateWorkflowResponse
newCreateWorkflowResponse Int
pHttpStatus_ =
  CreateWorkflowResponse'
    { $sel:adsApplicationConfigurationId:CreateWorkflowResponse' :: Maybe Text
adsApplicationConfigurationId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:arn:CreateWorkflowResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:CreateWorkflowResponse' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:description:CreateWorkflowResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:id:CreateWorkflowResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CreateWorkflowResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:status:CreateWorkflowResponse' :: Maybe MigrationWorkflowStatusEnum
status = forall a. Maybe a
Prelude.Nothing,
      $sel:stepTargets:CreateWorkflowResponse' :: Maybe [Text]
stepTargets = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateWorkflowResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:templateId:CreateWorkflowResponse' :: Maybe Text
templateId = forall a. Maybe a
Prelude.Nothing,
      $sel:workflowInputs:CreateWorkflowResponse' :: Maybe (Sensitive (HashMap Text StepInput))
workflowInputs = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateWorkflowResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The configuration ID of the application configured in Application
-- Discovery Service.
createWorkflowResponse_adsApplicationConfigurationId :: Lens.Lens' CreateWorkflowResponse (Prelude.Maybe Prelude.Text)
createWorkflowResponse_adsApplicationConfigurationId :: Lens' CreateWorkflowResponse (Maybe Text)
createWorkflowResponse_adsApplicationConfigurationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkflowResponse' {Maybe Text
adsApplicationConfigurationId :: Maybe Text
$sel:adsApplicationConfigurationId:CreateWorkflowResponse' :: CreateWorkflowResponse -> Maybe Text
adsApplicationConfigurationId} -> Maybe Text
adsApplicationConfigurationId) (\s :: CreateWorkflowResponse
s@CreateWorkflowResponse' {} Maybe Text
a -> CreateWorkflowResponse
s {$sel:adsApplicationConfigurationId:CreateWorkflowResponse' :: Maybe Text
adsApplicationConfigurationId = Maybe Text
a} :: CreateWorkflowResponse)

-- | The Amazon Resource Name (ARN) of the migration workflow.
createWorkflowResponse_arn :: Lens.Lens' CreateWorkflowResponse (Prelude.Maybe Prelude.Text)
createWorkflowResponse_arn :: Lens' CreateWorkflowResponse (Maybe Text)
createWorkflowResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkflowResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:CreateWorkflowResponse' :: CreateWorkflowResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: CreateWorkflowResponse
s@CreateWorkflowResponse' {} Maybe Text
a -> CreateWorkflowResponse
s {$sel:arn:CreateWorkflowResponse' :: Maybe Text
arn = Maybe Text
a} :: CreateWorkflowResponse)

-- | The time at which the migration workflow was created.
createWorkflowResponse_creationTime :: Lens.Lens' CreateWorkflowResponse (Prelude.Maybe Prelude.UTCTime)
createWorkflowResponse_creationTime :: Lens' CreateWorkflowResponse (Maybe UTCTime)
createWorkflowResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkflowResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:CreateWorkflowResponse' :: CreateWorkflowResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: CreateWorkflowResponse
s@CreateWorkflowResponse' {} Maybe POSIX
a -> CreateWorkflowResponse
s {$sel:creationTime:CreateWorkflowResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: CreateWorkflowResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

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

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

-- | The name of the migration workflow.
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 status of the migration workflow.
createWorkflowResponse_status :: Lens.Lens' CreateWorkflowResponse (Prelude.Maybe MigrationWorkflowStatusEnum)
createWorkflowResponse_status :: Lens' CreateWorkflowResponse (Maybe MigrationWorkflowStatusEnum)
createWorkflowResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkflowResponse' {Maybe MigrationWorkflowStatusEnum
status :: Maybe MigrationWorkflowStatusEnum
$sel:status:CreateWorkflowResponse' :: CreateWorkflowResponse -> Maybe MigrationWorkflowStatusEnum
status} -> Maybe MigrationWorkflowStatusEnum
status) (\s :: CreateWorkflowResponse
s@CreateWorkflowResponse' {} Maybe MigrationWorkflowStatusEnum
a -> CreateWorkflowResponse
s {$sel:status:CreateWorkflowResponse' :: Maybe MigrationWorkflowStatusEnum
status = Maybe MigrationWorkflowStatusEnum
a} :: CreateWorkflowResponse)

-- | The servers on which a step will be run.
createWorkflowResponse_stepTargets :: Lens.Lens' CreateWorkflowResponse (Prelude.Maybe [Prelude.Text])
createWorkflowResponse_stepTargets :: Lens' CreateWorkflowResponse (Maybe [Text])
createWorkflowResponse_stepTargets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkflowResponse' {Maybe [Text]
stepTargets :: Maybe [Text]
$sel:stepTargets:CreateWorkflowResponse' :: CreateWorkflowResponse -> Maybe [Text]
stepTargets} -> Maybe [Text]
stepTargets) (\s :: CreateWorkflowResponse
s@CreateWorkflowResponse' {} Maybe [Text]
a -> CreateWorkflowResponse
s {$sel:stepTargets:CreateWorkflowResponse' :: Maybe [Text]
stepTargets = Maybe [Text]
a} :: CreateWorkflowResponse) 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 tags to add on a migration workflow.
createWorkflowResponse_tags :: Lens.Lens' CreateWorkflowResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createWorkflowResponse_tags :: Lens' CreateWorkflowResponse (Maybe (HashMap Text Text))
createWorkflowResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkflowResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateWorkflowResponse' :: CreateWorkflowResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateWorkflowResponse
s@CreateWorkflowResponse' {} Maybe (HashMap Text Text)
a -> CreateWorkflowResponse
s {$sel:tags:CreateWorkflowResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateWorkflowResponse) 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 ID of the template.
createWorkflowResponse_templateId :: Lens.Lens' CreateWorkflowResponse (Prelude.Maybe Prelude.Text)
createWorkflowResponse_templateId :: Lens' CreateWorkflowResponse (Maybe Text)
createWorkflowResponse_templateId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkflowResponse' {Maybe Text
templateId :: Maybe Text
$sel:templateId:CreateWorkflowResponse' :: CreateWorkflowResponse -> Maybe Text
templateId} -> Maybe Text
templateId) (\s :: CreateWorkflowResponse
s@CreateWorkflowResponse' {} Maybe Text
a -> CreateWorkflowResponse
s {$sel:templateId:CreateWorkflowResponse' :: Maybe Text
templateId = Maybe Text
a} :: CreateWorkflowResponse)

-- | The inputs for creating a migration workflow.
createWorkflowResponse_workflowInputs :: Lens.Lens' CreateWorkflowResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text StepInput))
createWorkflowResponse_workflowInputs :: Lens' CreateWorkflowResponse (Maybe (HashMap Text StepInput))
createWorkflowResponse_workflowInputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkflowResponse' {Maybe (Sensitive (HashMap Text StepInput))
workflowInputs :: Maybe (Sensitive (HashMap Text StepInput))
$sel:workflowInputs:CreateWorkflowResponse' :: CreateWorkflowResponse
-> Maybe (Sensitive (HashMap Text StepInput))
workflowInputs} -> Maybe (Sensitive (HashMap Text StepInput))
workflowInputs) (\s :: CreateWorkflowResponse
s@CreateWorkflowResponse' {} Maybe (Sensitive (HashMap Text StepInput))
a -> CreateWorkflowResponse
s {$sel:workflowInputs:CreateWorkflowResponse' :: Maybe (Sensitive (HashMap Text StepInput))
workflowInputs = Maybe (Sensitive (HashMap Text StepInput))
a} :: CreateWorkflowResponse) 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 a. Iso' (Sensitive a) a
Data._Sensitive 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)

-- | 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]
Maybe Text
Maybe (HashMap Text Text)
Maybe (Sensitive (HashMap Text StepInput))
Maybe POSIX
Maybe MigrationWorkflowStatusEnum
httpStatus :: Int
workflowInputs :: Maybe (Sensitive (HashMap Text StepInput))
templateId :: Maybe Text
tags :: Maybe (HashMap Text Text)
stepTargets :: Maybe [Text]
status :: Maybe MigrationWorkflowStatusEnum
name :: Maybe Text
id :: Maybe Text
description :: Maybe Text
creationTime :: Maybe POSIX
arn :: Maybe Text
adsApplicationConfigurationId :: Maybe Text
$sel:httpStatus:CreateWorkflowResponse' :: CreateWorkflowResponse -> Int
$sel:workflowInputs:CreateWorkflowResponse' :: CreateWorkflowResponse
-> Maybe (Sensitive (HashMap Text StepInput))
$sel:templateId:CreateWorkflowResponse' :: CreateWorkflowResponse -> Maybe Text
$sel:tags:CreateWorkflowResponse' :: CreateWorkflowResponse -> Maybe (HashMap Text Text)
$sel:stepTargets:CreateWorkflowResponse' :: CreateWorkflowResponse -> Maybe [Text]
$sel:status:CreateWorkflowResponse' :: CreateWorkflowResponse -> Maybe MigrationWorkflowStatusEnum
$sel:name:CreateWorkflowResponse' :: CreateWorkflowResponse -> Maybe Text
$sel:id:CreateWorkflowResponse' :: CreateWorkflowResponse -> Maybe Text
$sel:description:CreateWorkflowResponse' :: CreateWorkflowResponse -> Maybe Text
$sel:creationTime:CreateWorkflowResponse' :: CreateWorkflowResponse -> Maybe POSIX
$sel:arn:CreateWorkflowResponse' :: CreateWorkflowResponse -> Maybe Text
$sel:adsApplicationConfigurationId:CreateWorkflowResponse' :: CreateWorkflowResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
adsApplicationConfigurationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
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 MigrationWorkflowStatusEnum
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
stepTargets
      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 Maybe Text
templateId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive (HashMap Text StepInput))
workflowInputs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus