{-# 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.SWF.DescribeWorkflowType
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns information about the specified /workflow type/. This includes
-- configuration settings specified when the type was registered and other
-- information such as creation date, current status, etc.
--
-- __Access Control__
--
-- You can use IAM policies to control this action\'s access to Amazon SWF
-- resources as follows:
--
-- -   Use a @Resource@ element with the domain name to limit the action to
--     only specified domains.
--
-- -   Use an @Action@ element to allow or deny permission to call this
--     action.
--
-- -   Constrain the following parameters by using a @Condition@ element
--     with the appropriate keys.
--
--     -   @workflowType.name@: String constraint. The key is
--         @swf:workflowType.name@.
--
--     -   @workflowType.version@: String constraint. The key is
--         @swf:workflowType.version@.
--
-- If the caller doesn\'t have sufficient permissions to invoke the action,
-- or the parameter values fall outside the specified constraints, the
-- action fails. The associated event attribute\'s @cause@ parameter is set
-- to @OPERATION_NOT_PERMITTED@. For details and example IAM policies, see
-- <https://docs.aws.amazon.com/amazonswf/latest/developerguide/swf-dev-iam.html Using IAM to Manage Access to Amazon SWF Workflows>
-- in the /Amazon SWF Developer Guide/.
module Amazonka.SWF.DescribeWorkflowType
  ( -- * Creating a Request
    DescribeWorkflowType (..),
    newDescribeWorkflowType,

    -- * Request Lenses
    describeWorkflowType_domain,
    describeWorkflowType_workflowType,

    -- * Destructuring the Response
    DescribeWorkflowTypeResponse (..),
    newDescribeWorkflowTypeResponse,

    -- * Response Lenses
    describeWorkflowTypeResponse_httpStatus,
    describeWorkflowTypeResponse_typeInfo,
    describeWorkflowTypeResponse_configuration,
  )
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.SWF.Types

-- | /See:/ 'newDescribeWorkflowType' smart constructor.
data DescribeWorkflowType = DescribeWorkflowType'
  { -- | The name of the domain in which this workflow type is registered.
    DescribeWorkflowType -> Text
domain :: Prelude.Text,
    -- | The workflow type to describe.
    DescribeWorkflowType -> WorkflowType
workflowType :: WorkflowType
  }
  deriving (DescribeWorkflowType -> DescribeWorkflowType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeWorkflowType -> DescribeWorkflowType -> Bool
$c/= :: DescribeWorkflowType -> DescribeWorkflowType -> Bool
== :: DescribeWorkflowType -> DescribeWorkflowType -> Bool
$c== :: DescribeWorkflowType -> DescribeWorkflowType -> Bool
Prelude.Eq, ReadPrec [DescribeWorkflowType]
ReadPrec DescribeWorkflowType
Int -> ReadS DescribeWorkflowType
ReadS [DescribeWorkflowType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeWorkflowType]
$creadListPrec :: ReadPrec [DescribeWorkflowType]
readPrec :: ReadPrec DescribeWorkflowType
$creadPrec :: ReadPrec DescribeWorkflowType
readList :: ReadS [DescribeWorkflowType]
$creadList :: ReadS [DescribeWorkflowType]
readsPrec :: Int -> ReadS DescribeWorkflowType
$creadsPrec :: Int -> ReadS DescribeWorkflowType
Prelude.Read, Int -> DescribeWorkflowType -> ShowS
[DescribeWorkflowType] -> ShowS
DescribeWorkflowType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeWorkflowType] -> ShowS
$cshowList :: [DescribeWorkflowType] -> ShowS
show :: DescribeWorkflowType -> String
$cshow :: DescribeWorkflowType -> String
showsPrec :: Int -> DescribeWorkflowType -> ShowS
$cshowsPrec :: Int -> DescribeWorkflowType -> ShowS
Prelude.Show, forall x. Rep DescribeWorkflowType x -> DescribeWorkflowType
forall x. DescribeWorkflowType -> Rep DescribeWorkflowType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeWorkflowType x -> DescribeWorkflowType
$cfrom :: forall x. DescribeWorkflowType -> Rep DescribeWorkflowType x
Prelude.Generic)

-- |
-- Create a value of 'DescribeWorkflowType' 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:
--
-- 'domain', 'describeWorkflowType_domain' - The name of the domain in which this workflow type is registered.
--
-- 'workflowType', 'describeWorkflowType_workflowType' - The workflow type to describe.
newDescribeWorkflowType ::
  -- | 'domain'
  Prelude.Text ->
  -- | 'workflowType'
  WorkflowType ->
  DescribeWorkflowType
newDescribeWorkflowType :: Text -> WorkflowType -> DescribeWorkflowType
newDescribeWorkflowType Text
pDomain_ WorkflowType
pWorkflowType_ =
  DescribeWorkflowType'
    { $sel:domain:DescribeWorkflowType' :: Text
domain = Text
pDomain_,
      $sel:workflowType:DescribeWorkflowType' :: WorkflowType
workflowType = WorkflowType
pWorkflowType_
    }

-- | The name of the domain in which this workflow type is registered.
describeWorkflowType_domain :: Lens.Lens' DescribeWorkflowType Prelude.Text
describeWorkflowType_domain :: Lens' DescribeWorkflowType Text
describeWorkflowType_domain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWorkflowType' {Text
domain :: Text
$sel:domain:DescribeWorkflowType' :: DescribeWorkflowType -> Text
domain} -> Text
domain) (\s :: DescribeWorkflowType
s@DescribeWorkflowType' {} Text
a -> DescribeWorkflowType
s {$sel:domain:DescribeWorkflowType' :: Text
domain = Text
a} :: DescribeWorkflowType)

-- | The workflow type to describe.
describeWorkflowType_workflowType :: Lens.Lens' DescribeWorkflowType WorkflowType
describeWorkflowType_workflowType :: Lens' DescribeWorkflowType WorkflowType
describeWorkflowType_workflowType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWorkflowType' {WorkflowType
workflowType :: WorkflowType
$sel:workflowType:DescribeWorkflowType' :: DescribeWorkflowType -> WorkflowType
workflowType} -> WorkflowType
workflowType) (\s :: DescribeWorkflowType
s@DescribeWorkflowType' {} WorkflowType
a -> DescribeWorkflowType
s {$sel:workflowType:DescribeWorkflowType' :: WorkflowType
workflowType = WorkflowType
a} :: DescribeWorkflowType)

instance Core.AWSRequest DescribeWorkflowType where
  type
    AWSResponse DescribeWorkflowType =
      DescribeWorkflowTypeResponse
  request :: (Service -> Service)
-> DescribeWorkflowType -> Request DescribeWorkflowType
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 DescribeWorkflowType
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeWorkflowType)))
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
-> WorkflowTypeInfo
-> WorkflowTypeConfiguration
-> DescribeWorkflowTypeResponse
DescribeWorkflowTypeResponse'
            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
"typeInfo")
            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
"configuration")
      )

instance Prelude.Hashable DescribeWorkflowType where
  hashWithSalt :: Int -> DescribeWorkflowType -> Int
hashWithSalt Int
_salt DescribeWorkflowType' {Text
WorkflowType
workflowType :: WorkflowType
domain :: Text
$sel:workflowType:DescribeWorkflowType' :: DescribeWorkflowType -> WorkflowType
$sel:domain:DescribeWorkflowType' :: DescribeWorkflowType -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
domain
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` WorkflowType
workflowType

instance Prelude.NFData DescribeWorkflowType where
  rnf :: DescribeWorkflowType -> ()
rnf DescribeWorkflowType' {Text
WorkflowType
workflowType :: WorkflowType
domain :: Text
$sel:workflowType:DescribeWorkflowType' :: DescribeWorkflowType -> WorkflowType
$sel:domain:DescribeWorkflowType' :: DescribeWorkflowType -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
domain
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf WorkflowType
workflowType

instance Data.ToHeaders DescribeWorkflowType where
  toHeaders :: DescribeWorkflowType -> 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
"SimpleWorkflowService.DescribeWorkflowType" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DescribeWorkflowType where
  toJSON :: DescribeWorkflowType -> Value
toJSON DescribeWorkflowType' {Text
WorkflowType
workflowType :: WorkflowType
domain :: Text
$sel:workflowType:DescribeWorkflowType' :: DescribeWorkflowType -> WorkflowType
$sel:domain:DescribeWorkflowType' :: DescribeWorkflowType -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"domain" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
domain),
            forall a. a -> Maybe a
Prelude.Just (Key
"workflowType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= WorkflowType
workflowType)
          ]
      )

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

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

-- | Contains details about a workflow type.
--
-- /See:/ 'newDescribeWorkflowTypeResponse' smart constructor.
data DescribeWorkflowTypeResponse = DescribeWorkflowTypeResponse'
  { -- | The response's http status code.
    DescribeWorkflowTypeResponse -> Int
httpStatus :: Prelude.Int,
    -- | General information about the workflow type.
    --
    -- The status of the workflow type (returned in the WorkflowTypeInfo
    -- structure) can be one of the following.
    --
    -- -   @REGISTERED@ – The type is registered and available. Workers
    --     supporting this type should be running.
    --
    -- -   @DEPRECATED@ – The type was deprecated using DeprecateWorkflowType,
    --     but is still in use. You should keep workers supporting this type
    --     running. You cannot create new workflow executions of this type.
    DescribeWorkflowTypeResponse -> WorkflowTypeInfo
typeInfo :: WorkflowTypeInfo,
    -- | Configuration settings of the workflow type registered through
    -- RegisterWorkflowType
    DescribeWorkflowTypeResponse -> WorkflowTypeConfiguration
configuration :: WorkflowTypeConfiguration
  }
  deriving (DescribeWorkflowTypeResponse
-> DescribeWorkflowTypeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeWorkflowTypeResponse
-> DescribeWorkflowTypeResponse -> Bool
$c/= :: DescribeWorkflowTypeResponse
-> DescribeWorkflowTypeResponse -> Bool
== :: DescribeWorkflowTypeResponse
-> DescribeWorkflowTypeResponse -> Bool
$c== :: DescribeWorkflowTypeResponse
-> DescribeWorkflowTypeResponse -> Bool
Prelude.Eq, ReadPrec [DescribeWorkflowTypeResponse]
ReadPrec DescribeWorkflowTypeResponse
Int -> ReadS DescribeWorkflowTypeResponse
ReadS [DescribeWorkflowTypeResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeWorkflowTypeResponse]
$creadListPrec :: ReadPrec [DescribeWorkflowTypeResponse]
readPrec :: ReadPrec DescribeWorkflowTypeResponse
$creadPrec :: ReadPrec DescribeWorkflowTypeResponse
readList :: ReadS [DescribeWorkflowTypeResponse]
$creadList :: ReadS [DescribeWorkflowTypeResponse]
readsPrec :: Int -> ReadS DescribeWorkflowTypeResponse
$creadsPrec :: Int -> ReadS DescribeWorkflowTypeResponse
Prelude.Read, Int -> DescribeWorkflowTypeResponse -> ShowS
[DescribeWorkflowTypeResponse] -> ShowS
DescribeWorkflowTypeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeWorkflowTypeResponse] -> ShowS
$cshowList :: [DescribeWorkflowTypeResponse] -> ShowS
show :: DescribeWorkflowTypeResponse -> String
$cshow :: DescribeWorkflowTypeResponse -> String
showsPrec :: Int -> DescribeWorkflowTypeResponse -> ShowS
$cshowsPrec :: Int -> DescribeWorkflowTypeResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeWorkflowTypeResponse x -> DescribeWorkflowTypeResponse
forall x.
DescribeWorkflowTypeResponse -> Rep DescribeWorkflowTypeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeWorkflowTypeResponse x -> DescribeWorkflowTypeResponse
$cfrom :: forall x.
DescribeWorkflowTypeResponse -> Rep DescribeWorkflowTypeResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeWorkflowTypeResponse' 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', 'describeWorkflowTypeResponse_httpStatus' - The response's http status code.
--
-- 'typeInfo', 'describeWorkflowTypeResponse_typeInfo' - General information about the workflow type.
--
-- The status of the workflow type (returned in the WorkflowTypeInfo
-- structure) can be one of the following.
--
-- -   @REGISTERED@ – The type is registered and available. Workers
--     supporting this type should be running.
--
-- -   @DEPRECATED@ – The type was deprecated using DeprecateWorkflowType,
--     but is still in use. You should keep workers supporting this type
--     running. You cannot create new workflow executions of this type.
--
-- 'configuration', 'describeWorkflowTypeResponse_configuration' - Configuration settings of the workflow type registered through
-- RegisterWorkflowType
newDescribeWorkflowTypeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'typeInfo'
  WorkflowTypeInfo ->
  -- | 'configuration'
  WorkflowTypeConfiguration ->
  DescribeWorkflowTypeResponse
newDescribeWorkflowTypeResponse :: Int
-> WorkflowTypeInfo
-> WorkflowTypeConfiguration
-> DescribeWorkflowTypeResponse
newDescribeWorkflowTypeResponse
  Int
pHttpStatus_
  WorkflowTypeInfo
pTypeInfo_
  WorkflowTypeConfiguration
pConfiguration_ =
    DescribeWorkflowTypeResponse'
      { $sel:httpStatus:DescribeWorkflowTypeResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:typeInfo:DescribeWorkflowTypeResponse' :: WorkflowTypeInfo
typeInfo = WorkflowTypeInfo
pTypeInfo_,
        $sel:configuration:DescribeWorkflowTypeResponse' :: WorkflowTypeConfiguration
configuration = WorkflowTypeConfiguration
pConfiguration_
      }

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

-- | General information about the workflow type.
--
-- The status of the workflow type (returned in the WorkflowTypeInfo
-- structure) can be one of the following.
--
-- -   @REGISTERED@ – The type is registered and available. Workers
--     supporting this type should be running.
--
-- -   @DEPRECATED@ – The type was deprecated using DeprecateWorkflowType,
--     but is still in use. You should keep workers supporting this type
--     running. You cannot create new workflow executions of this type.
describeWorkflowTypeResponse_typeInfo :: Lens.Lens' DescribeWorkflowTypeResponse WorkflowTypeInfo
describeWorkflowTypeResponse_typeInfo :: Lens' DescribeWorkflowTypeResponse WorkflowTypeInfo
describeWorkflowTypeResponse_typeInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWorkflowTypeResponse' {WorkflowTypeInfo
typeInfo :: WorkflowTypeInfo
$sel:typeInfo:DescribeWorkflowTypeResponse' :: DescribeWorkflowTypeResponse -> WorkflowTypeInfo
typeInfo} -> WorkflowTypeInfo
typeInfo) (\s :: DescribeWorkflowTypeResponse
s@DescribeWorkflowTypeResponse' {} WorkflowTypeInfo
a -> DescribeWorkflowTypeResponse
s {$sel:typeInfo:DescribeWorkflowTypeResponse' :: WorkflowTypeInfo
typeInfo = WorkflowTypeInfo
a} :: DescribeWorkflowTypeResponse)

-- | Configuration settings of the workflow type registered through
-- RegisterWorkflowType
describeWorkflowTypeResponse_configuration :: Lens.Lens' DescribeWorkflowTypeResponse WorkflowTypeConfiguration
describeWorkflowTypeResponse_configuration :: Lens' DescribeWorkflowTypeResponse WorkflowTypeConfiguration
describeWorkflowTypeResponse_configuration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWorkflowTypeResponse' {WorkflowTypeConfiguration
configuration :: WorkflowTypeConfiguration
$sel:configuration:DescribeWorkflowTypeResponse' :: DescribeWorkflowTypeResponse -> WorkflowTypeConfiguration
configuration} -> WorkflowTypeConfiguration
configuration) (\s :: DescribeWorkflowTypeResponse
s@DescribeWorkflowTypeResponse' {} WorkflowTypeConfiguration
a -> DescribeWorkflowTypeResponse
s {$sel:configuration:DescribeWorkflowTypeResponse' :: WorkflowTypeConfiguration
configuration = WorkflowTypeConfiguration
a} :: DescribeWorkflowTypeResponse)

instance Prelude.NFData DescribeWorkflowTypeResponse where
  rnf :: DescribeWorkflowTypeResponse -> ()
rnf DescribeWorkflowTypeResponse' {Int
WorkflowTypeConfiguration
WorkflowTypeInfo
configuration :: WorkflowTypeConfiguration
typeInfo :: WorkflowTypeInfo
httpStatus :: Int
$sel:configuration:DescribeWorkflowTypeResponse' :: DescribeWorkflowTypeResponse -> WorkflowTypeConfiguration
$sel:typeInfo:DescribeWorkflowTypeResponse' :: DescribeWorkflowTypeResponse -> WorkflowTypeInfo
$sel:httpStatus:DescribeWorkflowTypeResponse' :: DescribeWorkflowTypeResponse -> 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 WorkflowTypeInfo
typeInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf WorkflowTypeConfiguration
configuration