{-# 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.DescribeWorkflowExecution
-- 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 execution including its
-- type and some statistics.
--
-- This operation is eventually consistent. The results are best effort and
-- may not exactly reflect recent updates and changes.
--
-- __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.
--
-- -   You cannot use an IAM policy to constrain this action\'s parameters.
--
-- 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.DescribeWorkflowExecution
  ( -- * Creating a Request
    DescribeWorkflowExecution (..),
    newDescribeWorkflowExecution,

    -- * Request Lenses
    describeWorkflowExecution_domain,
    describeWorkflowExecution_execution,

    -- * Destructuring the Response
    DescribeWorkflowExecutionResponse (..),
    newDescribeWorkflowExecutionResponse,

    -- * Response Lenses
    describeWorkflowExecutionResponse_latestActivityTaskTimestamp,
    describeWorkflowExecutionResponse_latestExecutionContext,
    describeWorkflowExecutionResponse_httpStatus,
    describeWorkflowExecutionResponse_executionInfo,
    describeWorkflowExecutionResponse_executionConfiguration,
    describeWorkflowExecutionResponse_openCounts,
  )
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:/ 'newDescribeWorkflowExecution' smart constructor.
data DescribeWorkflowExecution = DescribeWorkflowExecution'
  { -- | The name of the domain containing the workflow execution.
    DescribeWorkflowExecution -> Text
domain :: Prelude.Text,
    -- | The workflow execution to describe.
    DescribeWorkflowExecution -> WorkflowExecution
execution :: WorkflowExecution
  }
  deriving (DescribeWorkflowExecution -> DescribeWorkflowExecution -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeWorkflowExecution -> DescribeWorkflowExecution -> Bool
$c/= :: DescribeWorkflowExecution -> DescribeWorkflowExecution -> Bool
== :: DescribeWorkflowExecution -> DescribeWorkflowExecution -> Bool
$c== :: DescribeWorkflowExecution -> DescribeWorkflowExecution -> Bool
Prelude.Eq, ReadPrec [DescribeWorkflowExecution]
ReadPrec DescribeWorkflowExecution
Int -> ReadS DescribeWorkflowExecution
ReadS [DescribeWorkflowExecution]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeWorkflowExecution]
$creadListPrec :: ReadPrec [DescribeWorkflowExecution]
readPrec :: ReadPrec DescribeWorkflowExecution
$creadPrec :: ReadPrec DescribeWorkflowExecution
readList :: ReadS [DescribeWorkflowExecution]
$creadList :: ReadS [DescribeWorkflowExecution]
readsPrec :: Int -> ReadS DescribeWorkflowExecution
$creadsPrec :: Int -> ReadS DescribeWorkflowExecution
Prelude.Read, Int -> DescribeWorkflowExecution -> ShowS
[DescribeWorkflowExecution] -> ShowS
DescribeWorkflowExecution -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeWorkflowExecution] -> ShowS
$cshowList :: [DescribeWorkflowExecution] -> ShowS
show :: DescribeWorkflowExecution -> String
$cshow :: DescribeWorkflowExecution -> String
showsPrec :: Int -> DescribeWorkflowExecution -> ShowS
$cshowsPrec :: Int -> DescribeWorkflowExecution -> ShowS
Prelude.Show, forall x.
Rep DescribeWorkflowExecution x -> DescribeWorkflowExecution
forall x.
DescribeWorkflowExecution -> Rep DescribeWorkflowExecution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeWorkflowExecution x -> DescribeWorkflowExecution
$cfrom :: forall x.
DescribeWorkflowExecution -> Rep DescribeWorkflowExecution x
Prelude.Generic)

-- |
-- Create a value of 'DescribeWorkflowExecution' 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', 'describeWorkflowExecution_domain' - The name of the domain containing the workflow execution.
--
-- 'execution', 'describeWorkflowExecution_execution' - The workflow execution to describe.
newDescribeWorkflowExecution ::
  -- | 'domain'
  Prelude.Text ->
  -- | 'execution'
  WorkflowExecution ->
  DescribeWorkflowExecution
newDescribeWorkflowExecution :: Text -> WorkflowExecution -> DescribeWorkflowExecution
newDescribeWorkflowExecution Text
pDomain_ WorkflowExecution
pExecution_ =
  DescribeWorkflowExecution'
    { $sel:domain:DescribeWorkflowExecution' :: Text
domain = Text
pDomain_,
      $sel:execution:DescribeWorkflowExecution' :: WorkflowExecution
execution = WorkflowExecution
pExecution_
    }

-- | The name of the domain containing the workflow execution.
describeWorkflowExecution_domain :: Lens.Lens' DescribeWorkflowExecution Prelude.Text
describeWorkflowExecution_domain :: Lens' DescribeWorkflowExecution Text
describeWorkflowExecution_domain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWorkflowExecution' {Text
domain :: Text
$sel:domain:DescribeWorkflowExecution' :: DescribeWorkflowExecution -> Text
domain} -> Text
domain) (\s :: DescribeWorkflowExecution
s@DescribeWorkflowExecution' {} Text
a -> DescribeWorkflowExecution
s {$sel:domain:DescribeWorkflowExecution' :: Text
domain = Text
a} :: DescribeWorkflowExecution)

-- | The workflow execution to describe.
describeWorkflowExecution_execution :: Lens.Lens' DescribeWorkflowExecution WorkflowExecution
describeWorkflowExecution_execution :: Lens' DescribeWorkflowExecution WorkflowExecution
describeWorkflowExecution_execution = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWorkflowExecution' {WorkflowExecution
execution :: WorkflowExecution
$sel:execution:DescribeWorkflowExecution' :: DescribeWorkflowExecution -> WorkflowExecution
execution} -> WorkflowExecution
execution) (\s :: DescribeWorkflowExecution
s@DescribeWorkflowExecution' {} WorkflowExecution
a -> DescribeWorkflowExecution
s {$sel:execution:DescribeWorkflowExecution' :: WorkflowExecution
execution = WorkflowExecution
a} :: DescribeWorkflowExecution)

instance Core.AWSRequest DescribeWorkflowExecution where
  type
    AWSResponse DescribeWorkflowExecution =
      DescribeWorkflowExecutionResponse
  request :: (Service -> Service)
-> DescribeWorkflowExecution -> Request DescribeWorkflowExecution
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 DescribeWorkflowExecution
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeWorkflowExecution)))
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 POSIX
-> Maybe Text
-> Int
-> WorkflowExecutionInfo
-> WorkflowExecutionConfiguration
-> WorkflowExecutionOpenCounts
-> DescribeWorkflowExecutionResponse
DescribeWorkflowExecutionResponse'
            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
"latestActivityTaskTimestamp")
            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
"latestExecutionContext")
            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))
            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
"executionInfo")
            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
"executionConfiguration")
            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
"openCounts")
      )

instance Prelude.Hashable DescribeWorkflowExecution where
  hashWithSalt :: Int -> DescribeWorkflowExecution -> Int
hashWithSalt Int
_salt DescribeWorkflowExecution' {Text
WorkflowExecution
execution :: WorkflowExecution
domain :: Text
$sel:execution:DescribeWorkflowExecution' :: DescribeWorkflowExecution -> WorkflowExecution
$sel:domain:DescribeWorkflowExecution' :: DescribeWorkflowExecution -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
domain
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` WorkflowExecution
execution

instance Prelude.NFData DescribeWorkflowExecution where
  rnf :: DescribeWorkflowExecution -> ()
rnf DescribeWorkflowExecution' {Text
WorkflowExecution
execution :: WorkflowExecution
domain :: Text
$sel:execution:DescribeWorkflowExecution' :: DescribeWorkflowExecution -> WorkflowExecution
$sel:domain:DescribeWorkflowExecution' :: DescribeWorkflowExecution -> 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 WorkflowExecution
execution

instance Data.ToHeaders DescribeWorkflowExecution where
  toHeaders :: DescribeWorkflowExecution -> 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.DescribeWorkflowExecution" ::
                          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 DescribeWorkflowExecution where
  toJSON :: DescribeWorkflowExecution -> Value
toJSON DescribeWorkflowExecution' {Text
WorkflowExecution
execution :: WorkflowExecution
domain :: Text
$sel:execution:DescribeWorkflowExecution' :: DescribeWorkflowExecution -> WorkflowExecution
$sel:domain:DescribeWorkflowExecution' :: DescribeWorkflowExecution -> 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
"execution" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= WorkflowExecution
execution)
          ]
      )

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

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

-- | Contains details about a workflow execution.
--
-- /See:/ 'newDescribeWorkflowExecutionResponse' smart constructor.
data DescribeWorkflowExecutionResponse = DescribeWorkflowExecutionResponse'
  { -- | The time when the last activity task was scheduled for this workflow
    -- execution. You can use this information to determine if the workflow has
    -- not made progress for an unusually long period of time and might require
    -- a corrective action.
    DescribeWorkflowExecutionResponse -> Maybe POSIX
latestActivityTaskTimestamp :: Prelude.Maybe Data.POSIX,
    -- | The latest executionContext provided by the decider for this workflow
    -- execution. A decider can provide an executionContext (a free-form
    -- string) when closing a decision task using RespondDecisionTaskCompleted.
    DescribeWorkflowExecutionResponse -> Maybe Text
latestExecutionContext :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeWorkflowExecutionResponse -> Int
httpStatus :: Prelude.Int,
    -- | Information about the workflow execution.
    DescribeWorkflowExecutionResponse -> WorkflowExecutionInfo
executionInfo :: WorkflowExecutionInfo,
    -- | The configuration settings for this workflow execution including timeout
    -- values, tasklist etc.
    DescribeWorkflowExecutionResponse -> WorkflowExecutionConfiguration
executionConfiguration :: WorkflowExecutionConfiguration,
    -- | The number of tasks for this workflow execution. This includes open and
    -- closed tasks of all types.
    DescribeWorkflowExecutionResponse -> WorkflowExecutionOpenCounts
openCounts :: WorkflowExecutionOpenCounts
  }
  deriving (DescribeWorkflowExecutionResponse
-> DescribeWorkflowExecutionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeWorkflowExecutionResponse
-> DescribeWorkflowExecutionResponse -> Bool
$c/= :: DescribeWorkflowExecutionResponse
-> DescribeWorkflowExecutionResponse -> Bool
== :: DescribeWorkflowExecutionResponse
-> DescribeWorkflowExecutionResponse -> Bool
$c== :: DescribeWorkflowExecutionResponse
-> DescribeWorkflowExecutionResponse -> Bool
Prelude.Eq, ReadPrec [DescribeWorkflowExecutionResponse]
ReadPrec DescribeWorkflowExecutionResponse
Int -> ReadS DescribeWorkflowExecutionResponse
ReadS [DescribeWorkflowExecutionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeWorkflowExecutionResponse]
$creadListPrec :: ReadPrec [DescribeWorkflowExecutionResponse]
readPrec :: ReadPrec DescribeWorkflowExecutionResponse
$creadPrec :: ReadPrec DescribeWorkflowExecutionResponse
readList :: ReadS [DescribeWorkflowExecutionResponse]
$creadList :: ReadS [DescribeWorkflowExecutionResponse]
readsPrec :: Int -> ReadS DescribeWorkflowExecutionResponse
$creadsPrec :: Int -> ReadS DescribeWorkflowExecutionResponse
Prelude.Read, Int -> DescribeWorkflowExecutionResponse -> ShowS
[DescribeWorkflowExecutionResponse] -> ShowS
DescribeWorkflowExecutionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeWorkflowExecutionResponse] -> ShowS
$cshowList :: [DescribeWorkflowExecutionResponse] -> ShowS
show :: DescribeWorkflowExecutionResponse -> String
$cshow :: DescribeWorkflowExecutionResponse -> String
showsPrec :: Int -> DescribeWorkflowExecutionResponse -> ShowS
$cshowsPrec :: Int -> DescribeWorkflowExecutionResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeWorkflowExecutionResponse x
-> DescribeWorkflowExecutionResponse
forall x.
DescribeWorkflowExecutionResponse
-> Rep DescribeWorkflowExecutionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeWorkflowExecutionResponse x
-> DescribeWorkflowExecutionResponse
$cfrom :: forall x.
DescribeWorkflowExecutionResponse
-> Rep DescribeWorkflowExecutionResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeWorkflowExecutionResponse' 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:
--
-- 'latestActivityTaskTimestamp', 'describeWorkflowExecutionResponse_latestActivityTaskTimestamp' - The time when the last activity task was scheduled for this workflow
-- execution. You can use this information to determine if the workflow has
-- not made progress for an unusually long period of time and might require
-- a corrective action.
--
-- 'latestExecutionContext', 'describeWorkflowExecutionResponse_latestExecutionContext' - The latest executionContext provided by the decider for this workflow
-- execution. A decider can provide an executionContext (a free-form
-- string) when closing a decision task using RespondDecisionTaskCompleted.
--
-- 'httpStatus', 'describeWorkflowExecutionResponse_httpStatus' - The response's http status code.
--
-- 'executionInfo', 'describeWorkflowExecutionResponse_executionInfo' - Information about the workflow execution.
--
-- 'executionConfiguration', 'describeWorkflowExecutionResponse_executionConfiguration' - The configuration settings for this workflow execution including timeout
-- values, tasklist etc.
--
-- 'openCounts', 'describeWorkflowExecutionResponse_openCounts' - The number of tasks for this workflow execution. This includes open and
-- closed tasks of all types.
newDescribeWorkflowExecutionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'executionInfo'
  WorkflowExecutionInfo ->
  -- | 'executionConfiguration'
  WorkflowExecutionConfiguration ->
  -- | 'openCounts'
  WorkflowExecutionOpenCounts ->
  DescribeWorkflowExecutionResponse
newDescribeWorkflowExecutionResponse :: Int
-> WorkflowExecutionInfo
-> WorkflowExecutionConfiguration
-> WorkflowExecutionOpenCounts
-> DescribeWorkflowExecutionResponse
newDescribeWorkflowExecutionResponse
  Int
pHttpStatus_
  WorkflowExecutionInfo
pExecutionInfo_
  WorkflowExecutionConfiguration
pExecutionConfiguration_
  WorkflowExecutionOpenCounts
pOpenCounts_ =
    DescribeWorkflowExecutionResponse'
      { $sel:latestActivityTaskTimestamp:DescribeWorkflowExecutionResponse' :: Maybe POSIX
latestActivityTaskTimestamp =
          forall a. Maybe a
Prelude.Nothing,
        $sel:latestExecutionContext:DescribeWorkflowExecutionResponse' :: Maybe Text
latestExecutionContext = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeWorkflowExecutionResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:executionInfo:DescribeWorkflowExecutionResponse' :: WorkflowExecutionInfo
executionInfo = WorkflowExecutionInfo
pExecutionInfo_,
        $sel:executionConfiguration:DescribeWorkflowExecutionResponse' :: WorkflowExecutionConfiguration
executionConfiguration =
          WorkflowExecutionConfiguration
pExecutionConfiguration_,
        $sel:openCounts:DescribeWorkflowExecutionResponse' :: WorkflowExecutionOpenCounts
openCounts = WorkflowExecutionOpenCounts
pOpenCounts_
      }

-- | The time when the last activity task was scheduled for this workflow
-- execution. You can use this information to determine if the workflow has
-- not made progress for an unusually long period of time and might require
-- a corrective action.
describeWorkflowExecutionResponse_latestActivityTaskTimestamp :: Lens.Lens' DescribeWorkflowExecutionResponse (Prelude.Maybe Prelude.UTCTime)
describeWorkflowExecutionResponse_latestActivityTaskTimestamp :: Lens' DescribeWorkflowExecutionResponse (Maybe UTCTime)
describeWorkflowExecutionResponse_latestActivityTaskTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWorkflowExecutionResponse' {Maybe POSIX
latestActivityTaskTimestamp :: Maybe POSIX
$sel:latestActivityTaskTimestamp:DescribeWorkflowExecutionResponse' :: DescribeWorkflowExecutionResponse -> Maybe POSIX
latestActivityTaskTimestamp} -> Maybe POSIX
latestActivityTaskTimestamp) (\s :: DescribeWorkflowExecutionResponse
s@DescribeWorkflowExecutionResponse' {} Maybe POSIX
a -> DescribeWorkflowExecutionResponse
s {$sel:latestActivityTaskTimestamp:DescribeWorkflowExecutionResponse' :: Maybe POSIX
latestActivityTaskTimestamp = Maybe POSIX
a} :: DescribeWorkflowExecutionResponse) 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 latest executionContext provided by the decider for this workflow
-- execution. A decider can provide an executionContext (a free-form
-- string) when closing a decision task using RespondDecisionTaskCompleted.
describeWorkflowExecutionResponse_latestExecutionContext :: Lens.Lens' DescribeWorkflowExecutionResponse (Prelude.Maybe Prelude.Text)
describeWorkflowExecutionResponse_latestExecutionContext :: Lens' DescribeWorkflowExecutionResponse (Maybe Text)
describeWorkflowExecutionResponse_latestExecutionContext = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWorkflowExecutionResponse' {Maybe Text
latestExecutionContext :: Maybe Text
$sel:latestExecutionContext:DescribeWorkflowExecutionResponse' :: DescribeWorkflowExecutionResponse -> Maybe Text
latestExecutionContext} -> Maybe Text
latestExecutionContext) (\s :: DescribeWorkflowExecutionResponse
s@DescribeWorkflowExecutionResponse' {} Maybe Text
a -> DescribeWorkflowExecutionResponse
s {$sel:latestExecutionContext:DescribeWorkflowExecutionResponse' :: Maybe Text
latestExecutionContext = Maybe Text
a} :: DescribeWorkflowExecutionResponse)

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

-- | Information about the workflow execution.
describeWorkflowExecutionResponse_executionInfo :: Lens.Lens' DescribeWorkflowExecutionResponse WorkflowExecutionInfo
describeWorkflowExecutionResponse_executionInfo :: Lens' DescribeWorkflowExecutionResponse WorkflowExecutionInfo
describeWorkflowExecutionResponse_executionInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWorkflowExecutionResponse' {WorkflowExecutionInfo
executionInfo :: WorkflowExecutionInfo
$sel:executionInfo:DescribeWorkflowExecutionResponse' :: DescribeWorkflowExecutionResponse -> WorkflowExecutionInfo
executionInfo} -> WorkflowExecutionInfo
executionInfo) (\s :: DescribeWorkflowExecutionResponse
s@DescribeWorkflowExecutionResponse' {} WorkflowExecutionInfo
a -> DescribeWorkflowExecutionResponse
s {$sel:executionInfo:DescribeWorkflowExecutionResponse' :: WorkflowExecutionInfo
executionInfo = WorkflowExecutionInfo
a} :: DescribeWorkflowExecutionResponse)

-- | The configuration settings for this workflow execution including timeout
-- values, tasklist etc.
describeWorkflowExecutionResponse_executionConfiguration :: Lens.Lens' DescribeWorkflowExecutionResponse WorkflowExecutionConfiguration
describeWorkflowExecutionResponse_executionConfiguration :: Lens'
  DescribeWorkflowExecutionResponse WorkflowExecutionConfiguration
describeWorkflowExecutionResponse_executionConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWorkflowExecutionResponse' {WorkflowExecutionConfiguration
executionConfiguration :: WorkflowExecutionConfiguration
$sel:executionConfiguration:DescribeWorkflowExecutionResponse' :: DescribeWorkflowExecutionResponse -> WorkflowExecutionConfiguration
executionConfiguration} -> WorkflowExecutionConfiguration
executionConfiguration) (\s :: DescribeWorkflowExecutionResponse
s@DescribeWorkflowExecutionResponse' {} WorkflowExecutionConfiguration
a -> DescribeWorkflowExecutionResponse
s {$sel:executionConfiguration:DescribeWorkflowExecutionResponse' :: WorkflowExecutionConfiguration
executionConfiguration = WorkflowExecutionConfiguration
a} :: DescribeWorkflowExecutionResponse)

-- | The number of tasks for this workflow execution. This includes open and
-- closed tasks of all types.
describeWorkflowExecutionResponse_openCounts :: Lens.Lens' DescribeWorkflowExecutionResponse WorkflowExecutionOpenCounts
describeWorkflowExecutionResponse_openCounts :: Lens' DescribeWorkflowExecutionResponse WorkflowExecutionOpenCounts
describeWorkflowExecutionResponse_openCounts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeWorkflowExecutionResponse' {WorkflowExecutionOpenCounts
openCounts :: WorkflowExecutionOpenCounts
$sel:openCounts:DescribeWorkflowExecutionResponse' :: DescribeWorkflowExecutionResponse -> WorkflowExecutionOpenCounts
openCounts} -> WorkflowExecutionOpenCounts
openCounts) (\s :: DescribeWorkflowExecutionResponse
s@DescribeWorkflowExecutionResponse' {} WorkflowExecutionOpenCounts
a -> DescribeWorkflowExecutionResponse
s {$sel:openCounts:DescribeWorkflowExecutionResponse' :: WorkflowExecutionOpenCounts
openCounts = WorkflowExecutionOpenCounts
a} :: DescribeWorkflowExecutionResponse)

instance
  Prelude.NFData
    DescribeWorkflowExecutionResponse
  where
  rnf :: DescribeWorkflowExecutionResponse -> ()
rnf DescribeWorkflowExecutionResponse' {Int
Maybe Text
Maybe POSIX
WorkflowExecutionConfiguration
WorkflowExecutionOpenCounts
WorkflowExecutionInfo
openCounts :: WorkflowExecutionOpenCounts
executionConfiguration :: WorkflowExecutionConfiguration
executionInfo :: WorkflowExecutionInfo
httpStatus :: Int
latestExecutionContext :: Maybe Text
latestActivityTaskTimestamp :: Maybe POSIX
$sel:openCounts:DescribeWorkflowExecutionResponse' :: DescribeWorkflowExecutionResponse -> WorkflowExecutionOpenCounts
$sel:executionConfiguration:DescribeWorkflowExecutionResponse' :: DescribeWorkflowExecutionResponse -> WorkflowExecutionConfiguration
$sel:executionInfo:DescribeWorkflowExecutionResponse' :: DescribeWorkflowExecutionResponse -> WorkflowExecutionInfo
$sel:httpStatus:DescribeWorkflowExecutionResponse' :: DescribeWorkflowExecutionResponse -> Int
$sel:latestExecutionContext:DescribeWorkflowExecutionResponse' :: DescribeWorkflowExecutionResponse -> Maybe Text
$sel:latestActivityTaskTimestamp:DescribeWorkflowExecutionResponse' :: DescribeWorkflowExecutionResponse -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
latestActivityTaskTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
latestExecutionContext
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 WorkflowExecutionInfo
executionInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf WorkflowExecutionConfiguration
executionConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf WorkflowExecutionOpenCounts
openCounts