{-# 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.PollForDecisionTask
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Used by deciders to get a DecisionTask from the specified decision
-- @taskList@. A decision task may be returned for any open workflow
-- execution that is using the specified task list. The task includes a
-- paginated view of the history of the workflow execution. The decider
-- should use the workflow type and the history to determine how to
-- properly handle the task.
--
-- This action initiates a long poll, where the service holds the HTTP
-- connection open and responds as soon a task becomes available. If no
-- decision task is available in the specified task list before the timeout
-- of 60 seconds expires, an empty result is returned. An empty result, in
-- this context, means that a DecisionTask is returned, but that the value
-- of taskToken is an empty string.
--
-- Deciders should set their client side socket timeout to at least 70
-- seconds (10 seconds higher than the timeout).
--
-- Because the number of workflow history events for a single workflow
-- execution might be very large, the result returned might be split up
-- across a number of pages. To retrieve subsequent pages, make additional
-- calls to @PollForDecisionTask@ using the @nextPageToken@ returned by the
-- initial call. Note that you do /not/ call @GetWorkflowExecutionHistory@
-- with this @nextPageToken@. Instead, call @PollForDecisionTask@ again.
--
-- __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 @taskList.name@ parameter by using a @Condition@
--     element with the @swf:taskList.name@ key to allow the action to
--     access only certain task lists.
--
-- 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/.
--
-- This operation returns paginated results.
module Amazonka.SWF.PollForDecisionTask
  ( -- * Creating a Request
    PollForDecisionTask (..),
    newPollForDecisionTask,

    -- * Request Lenses
    pollForDecisionTask_identity,
    pollForDecisionTask_maximumPageSize,
    pollForDecisionTask_nextPageToken,
    pollForDecisionTask_reverseOrder,
    pollForDecisionTask_domain,
    pollForDecisionTask_taskList,

    -- * Destructuring the Response
    PollForDecisionTaskResponse (..),
    newPollForDecisionTaskResponse,

    -- * Response Lenses
    pollForDecisionTaskResponse_events,
    pollForDecisionTaskResponse_nextPageToken,
    pollForDecisionTaskResponse_previousStartedEventId,
    pollForDecisionTaskResponse_taskToken,
    pollForDecisionTaskResponse_workflowExecution,
    pollForDecisionTaskResponse_workflowType,
    pollForDecisionTaskResponse_httpStatus,
    pollForDecisionTaskResponse_startedEventId,
  )
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:/ 'newPollForDecisionTask' smart constructor.
data PollForDecisionTask = PollForDecisionTask'
  { -- | Identity of the decider making the request, which is recorded in the
    -- DecisionTaskStarted event in the workflow history. This enables
    -- diagnostic tracing when problems arise. The form of this identity is
    -- user defined.
    PollForDecisionTask -> Maybe Text
identity :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of results that are returned per call. Use
    -- @nextPageToken@ to obtain further pages of results.
    --
    -- This is an upper limit only; the actual number of results returned per
    -- call may be fewer than the specified maximum.
    PollForDecisionTask -> Maybe Natural
maximumPageSize :: Prelude.Maybe Prelude.Natural,
    -- | If @NextPageToken@ is returned there are more results available. The
    -- value of @NextPageToken@ is a unique pagination token for each page.
    -- Make the call again using the returned token to retrieve the next page.
    -- Keep all other arguments unchanged. Each pagination token expires after
    -- 60 seconds. Using an expired pagination token will return a @400@ error:
    -- \"@Specified token has exceeded its maximum lifetime@\".
    --
    -- The configured @maximumPageSize@ determines how many results can be
    -- returned in a single call.
    --
    -- The @nextPageToken@ returned by this action cannot be used with
    -- GetWorkflowExecutionHistory to get the next page. You must call
    -- PollForDecisionTask again (with the @nextPageToken@) to retrieve the
    -- next page of history records. Calling PollForDecisionTask with a
    -- @nextPageToken@ doesn\'t return a new decision task.
    PollForDecisionTask -> Maybe Text
nextPageToken :: Prelude.Maybe Prelude.Text,
    -- | When set to @true@, returns the events in reverse order. By default the
    -- results are returned in ascending order of the @eventTimestamp@ of the
    -- events.
    PollForDecisionTask -> Maybe Bool
reverseOrder :: Prelude.Maybe Prelude.Bool,
    -- | The name of the domain containing the task lists to poll.
    PollForDecisionTask -> Text
domain :: Prelude.Text,
    -- | Specifies the task list to poll for decision tasks.
    --
    -- The specified string must not start or end with whitespace. It must not
    -- contain a @:@ (colon), @\/@ (slash), @|@ (vertical bar), or any control
    -- characters (@\\u0000-\\u001f@ | @\\u007f-\\u009f@). Also, it must not
    -- /be/ the literal string @arn@.
    PollForDecisionTask -> TaskList
taskList :: TaskList
  }
  deriving (PollForDecisionTask -> PollForDecisionTask -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PollForDecisionTask -> PollForDecisionTask -> Bool
$c/= :: PollForDecisionTask -> PollForDecisionTask -> Bool
== :: PollForDecisionTask -> PollForDecisionTask -> Bool
$c== :: PollForDecisionTask -> PollForDecisionTask -> Bool
Prelude.Eq, ReadPrec [PollForDecisionTask]
ReadPrec PollForDecisionTask
Int -> ReadS PollForDecisionTask
ReadS [PollForDecisionTask]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PollForDecisionTask]
$creadListPrec :: ReadPrec [PollForDecisionTask]
readPrec :: ReadPrec PollForDecisionTask
$creadPrec :: ReadPrec PollForDecisionTask
readList :: ReadS [PollForDecisionTask]
$creadList :: ReadS [PollForDecisionTask]
readsPrec :: Int -> ReadS PollForDecisionTask
$creadsPrec :: Int -> ReadS PollForDecisionTask
Prelude.Read, Int -> PollForDecisionTask -> ShowS
[PollForDecisionTask] -> ShowS
PollForDecisionTask -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PollForDecisionTask] -> ShowS
$cshowList :: [PollForDecisionTask] -> ShowS
show :: PollForDecisionTask -> String
$cshow :: PollForDecisionTask -> String
showsPrec :: Int -> PollForDecisionTask -> ShowS
$cshowsPrec :: Int -> PollForDecisionTask -> ShowS
Prelude.Show, forall x. Rep PollForDecisionTask x -> PollForDecisionTask
forall x. PollForDecisionTask -> Rep PollForDecisionTask x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PollForDecisionTask x -> PollForDecisionTask
$cfrom :: forall x. PollForDecisionTask -> Rep PollForDecisionTask x
Prelude.Generic)

-- |
-- Create a value of 'PollForDecisionTask' 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:
--
-- 'identity', 'pollForDecisionTask_identity' - Identity of the decider making the request, which is recorded in the
-- DecisionTaskStarted event in the workflow history. This enables
-- diagnostic tracing when problems arise. The form of this identity is
-- user defined.
--
-- 'maximumPageSize', 'pollForDecisionTask_maximumPageSize' - The maximum number of results that are returned per call. Use
-- @nextPageToken@ to obtain further pages of results.
--
-- This is an upper limit only; the actual number of results returned per
-- call may be fewer than the specified maximum.
--
-- 'nextPageToken', 'pollForDecisionTask_nextPageToken' - If @NextPageToken@ is returned there are more results available. The
-- value of @NextPageToken@ is a unique pagination token for each page.
-- Make the call again using the returned token to retrieve the next page.
-- Keep all other arguments unchanged. Each pagination token expires after
-- 60 seconds. Using an expired pagination token will return a @400@ error:
-- \"@Specified token has exceeded its maximum lifetime@\".
--
-- The configured @maximumPageSize@ determines how many results can be
-- returned in a single call.
--
-- The @nextPageToken@ returned by this action cannot be used with
-- GetWorkflowExecutionHistory to get the next page. You must call
-- PollForDecisionTask again (with the @nextPageToken@) to retrieve the
-- next page of history records. Calling PollForDecisionTask with a
-- @nextPageToken@ doesn\'t return a new decision task.
--
-- 'reverseOrder', 'pollForDecisionTask_reverseOrder' - When set to @true@, returns the events in reverse order. By default the
-- results are returned in ascending order of the @eventTimestamp@ of the
-- events.
--
-- 'domain', 'pollForDecisionTask_domain' - The name of the domain containing the task lists to poll.
--
-- 'taskList', 'pollForDecisionTask_taskList' - Specifies the task list to poll for decision tasks.
--
-- The specified string must not start or end with whitespace. It must not
-- contain a @:@ (colon), @\/@ (slash), @|@ (vertical bar), or any control
-- characters (@\\u0000-\\u001f@ | @\\u007f-\\u009f@). Also, it must not
-- /be/ the literal string @arn@.
newPollForDecisionTask ::
  -- | 'domain'
  Prelude.Text ->
  -- | 'taskList'
  TaskList ->
  PollForDecisionTask
newPollForDecisionTask :: Text -> TaskList -> PollForDecisionTask
newPollForDecisionTask Text
pDomain_ TaskList
pTaskList_ =
  PollForDecisionTask'
    { $sel:identity:PollForDecisionTask' :: Maybe Text
identity = forall a. Maybe a
Prelude.Nothing,
      $sel:maximumPageSize:PollForDecisionTask' :: Maybe Natural
maximumPageSize = forall a. Maybe a
Prelude.Nothing,
      $sel:nextPageToken:PollForDecisionTask' :: Maybe Text
nextPageToken = forall a. Maybe a
Prelude.Nothing,
      $sel:reverseOrder:PollForDecisionTask' :: Maybe Bool
reverseOrder = forall a. Maybe a
Prelude.Nothing,
      $sel:domain:PollForDecisionTask' :: Text
domain = Text
pDomain_,
      $sel:taskList:PollForDecisionTask' :: TaskList
taskList = TaskList
pTaskList_
    }

-- | Identity of the decider making the request, which is recorded in the
-- DecisionTaskStarted event in the workflow history. This enables
-- diagnostic tracing when problems arise. The form of this identity is
-- user defined.
pollForDecisionTask_identity :: Lens.Lens' PollForDecisionTask (Prelude.Maybe Prelude.Text)
pollForDecisionTask_identity :: Lens' PollForDecisionTask (Maybe Text)
pollForDecisionTask_identity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PollForDecisionTask' {Maybe Text
identity :: Maybe Text
$sel:identity:PollForDecisionTask' :: PollForDecisionTask -> Maybe Text
identity} -> Maybe Text
identity) (\s :: PollForDecisionTask
s@PollForDecisionTask' {} Maybe Text
a -> PollForDecisionTask
s {$sel:identity:PollForDecisionTask' :: Maybe Text
identity = Maybe Text
a} :: PollForDecisionTask)

-- | The maximum number of results that are returned per call. Use
-- @nextPageToken@ to obtain further pages of results.
--
-- This is an upper limit only; the actual number of results returned per
-- call may be fewer than the specified maximum.
pollForDecisionTask_maximumPageSize :: Lens.Lens' PollForDecisionTask (Prelude.Maybe Prelude.Natural)
pollForDecisionTask_maximumPageSize :: Lens' PollForDecisionTask (Maybe Natural)
pollForDecisionTask_maximumPageSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PollForDecisionTask' {Maybe Natural
maximumPageSize :: Maybe Natural
$sel:maximumPageSize:PollForDecisionTask' :: PollForDecisionTask -> Maybe Natural
maximumPageSize} -> Maybe Natural
maximumPageSize) (\s :: PollForDecisionTask
s@PollForDecisionTask' {} Maybe Natural
a -> PollForDecisionTask
s {$sel:maximumPageSize:PollForDecisionTask' :: Maybe Natural
maximumPageSize = Maybe Natural
a} :: PollForDecisionTask)

-- | If @NextPageToken@ is returned there are more results available. The
-- value of @NextPageToken@ is a unique pagination token for each page.
-- Make the call again using the returned token to retrieve the next page.
-- Keep all other arguments unchanged. Each pagination token expires after
-- 60 seconds. Using an expired pagination token will return a @400@ error:
-- \"@Specified token has exceeded its maximum lifetime@\".
--
-- The configured @maximumPageSize@ determines how many results can be
-- returned in a single call.
--
-- The @nextPageToken@ returned by this action cannot be used with
-- GetWorkflowExecutionHistory to get the next page. You must call
-- PollForDecisionTask again (with the @nextPageToken@) to retrieve the
-- next page of history records. Calling PollForDecisionTask with a
-- @nextPageToken@ doesn\'t return a new decision task.
pollForDecisionTask_nextPageToken :: Lens.Lens' PollForDecisionTask (Prelude.Maybe Prelude.Text)
pollForDecisionTask_nextPageToken :: Lens' PollForDecisionTask (Maybe Text)
pollForDecisionTask_nextPageToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PollForDecisionTask' {Maybe Text
nextPageToken :: Maybe Text
$sel:nextPageToken:PollForDecisionTask' :: PollForDecisionTask -> Maybe Text
nextPageToken} -> Maybe Text
nextPageToken) (\s :: PollForDecisionTask
s@PollForDecisionTask' {} Maybe Text
a -> PollForDecisionTask
s {$sel:nextPageToken:PollForDecisionTask' :: Maybe Text
nextPageToken = Maybe Text
a} :: PollForDecisionTask)

-- | When set to @true@, returns the events in reverse order. By default the
-- results are returned in ascending order of the @eventTimestamp@ of the
-- events.
pollForDecisionTask_reverseOrder :: Lens.Lens' PollForDecisionTask (Prelude.Maybe Prelude.Bool)
pollForDecisionTask_reverseOrder :: Lens' PollForDecisionTask (Maybe Bool)
pollForDecisionTask_reverseOrder = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PollForDecisionTask' {Maybe Bool
reverseOrder :: Maybe Bool
$sel:reverseOrder:PollForDecisionTask' :: PollForDecisionTask -> Maybe Bool
reverseOrder} -> Maybe Bool
reverseOrder) (\s :: PollForDecisionTask
s@PollForDecisionTask' {} Maybe Bool
a -> PollForDecisionTask
s {$sel:reverseOrder:PollForDecisionTask' :: Maybe Bool
reverseOrder = Maybe Bool
a} :: PollForDecisionTask)

-- | The name of the domain containing the task lists to poll.
pollForDecisionTask_domain :: Lens.Lens' PollForDecisionTask Prelude.Text
pollForDecisionTask_domain :: Lens' PollForDecisionTask Text
pollForDecisionTask_domain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PollForDecisionTask' {Text
domain :: Text
$sel:domain:PollForDecisionTask' :: PollForDecisionTask -> Text
domain} -> Text
domain) (\s :: PollForDecisionTask
s@PollForDecisionTask' {} Text
a -> PollForDecisionTask
s {$sel:domain:PollForDecisionTask' :: Text
domain = Text
a} :: PollForDecisionTask)

-- | Specifies the task list to poll for decision tasks.
--
-- The specified string must not start or end with whitespace. It must not
-- contain a @:@ (colon), @\/@ (slash), @|@ (vertical bar), or any control
-- characters (@\\u0000-\\u001f@ | @\\u007f-\\u009f@). Also, it must not
-- /be/ the literal string @arn@.
pollForDecisionTask_taskList :: Lens.Lens' PollForDecisionTask TaskList
pollForDecisionTask_taskList :: Lens' PollForDecisionTask TaskList
pollForDecisionTask_taskList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PollForDecisionTask' {TaskList
taskList :: TaskList
$sel:taskList:PollForDecisionTask' :: PollForDecisionTask -> TaskList
taskList} -> TaskList
taskList) (\s :: PollForDecisionTask
s@PollForDecisionTask' {} TaskList
a -> PollForDecisionTask
s {$sel:taskList:PollForDecisionTask' :: TaskList
taskList = TaskList
a} :: PollForDecisionTask)

instance Core.AWSPager PollForDecisionTask where
  page :: PollForDecisionTask
-> AWSResponse PollForDecisionTask -> Maybe PollForDecisionTask
page PollForDecisionTask
rq AWSResponse PollForDecisionTask
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse PollForDecisionTask
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' PollForDecisionTaskResponse (Maybe Text)
pollForDecisionTaskResponse_nextPageToken
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse PollForDecisionTask
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' PollForDecisionTaskResponse (Maybe [HistoryEvent])
pollForDecisionTaskResponse_events
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ PollForDecisionTask
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' PollForDecisionTask (Maybe Text)
pollForDecisionTask_nextPageToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse PollForDecisionTask
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' PollForDecisionTaskResponse (Maybe Text)
pollForDecisionTaskResponse_nextPageToken
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest PollForDecisionTask where
  type
    AWSResponse PollForDecisionTask =
      PollForDecisionTaskResponse
  request :: (Service -> Service)
-> PollForDecisionTask -> Request PollForDecisionTask
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 PollForDecisionTask
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse PollForDecisionTask)))
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 [HistoryEvent]
-> Maybe Text
-> Maybe Integer
-> Maybe Text
-> Maybe WorkflowExecution
-> Maybe WorkflowType
-> Int
-> Integer
-> PollForDecisionTaskResponse
PollForDecisionTaskResponse'
            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
"events" 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
"nextPageToken")
            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
"previousStartedEventId")
            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
"taskToken")
            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
"workflowExecution")
            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
"workflowType")
            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
"startedEventId")
      )

instance Prelude.Hashable PollForDecisionTask where
  hashWithSalt :: Int -> PollForDecisionTask -> Int
hashWithSalt Int
_salt PollForDecisionTask' {Maybe Bool
Maybe Natural
Maybe Text
Text
TaskList
taskList :: TaskList
domain :: Text
reverseOrder :: Maybe Bool
nextPageToken :: Maybe Text
maximumPageSize :: Maybe Natural
identity :: Maybe Text
$sel:taskList:PollForDecisionTask' :: PollForDecisionTask -> TaskList
$sel:domain:PollForDecisionTask' :: PollForDecisionTask -> Text
$sel:reverseOrder:PollForDecisionTask' :: PollForDecisionTask -> Maybe Bool
$sel:nextPageToken:PollForDecisionTask' :: PollForDecisionTask -> Maybe Text
$sel:maximumPageSize:PollForDecisionTask' :: PollForDecisionTask -> Maybe Natural
$sel:identity:PollForDecisionTask' :: PollForDecisionTask -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
identity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maximumPageSize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextPageToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
reverseOrder
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
domain
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` TaskList
taskList

instance Prelude.NFData PollForDecisionTask where
  rnf :: PollForDecisionTask -> ()
rnf PollForDecisionTask' {Maybe Bool
Maybe Natural
Maybe Text
Text
TaskList
taskList :: TaskList
domain :: Text
reverseOrder :: Maybe Bool
nextPageToken :: Maybe Text
maximumPageSize :: Maybe Natural
identity :: Maybe Text
$sel:taskList:PollForDecisionTask' :: PollForDecisionTask -> TaskList
$sel:domain:PollForDecisionTask' :: PollForDecisionTask -> Text
$sel:reverseOrder:PollForDecisionTask' :: PollForDecisionTask -> Maybe Bool
$sel:nextPageToken:PollForDecisionTask' :: PollForDecisionTask -> Maybe Text
$sel:maximumPageSize:PollForDecisionTask' :: PollForDecisionTask -> Maybe Natural
$sel:identity:PollForDecisionTask' :: PollForDecisionTask -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
identity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maximumPageSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextPageToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
reverseOrder
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 TaskList
taskList

instance Data.ToHeaders PollForDecisionTask where
  toHeaders :: PollForDecisionTask -> 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.PollForDecisionTask" ::
                          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 PollForDecisionTask where
  toJSON :: PollForDecisionTask -> Value
toJSON PollForDecisionTask' {Maybe Bool
Maybe Natural
Maybe Text
Text
TaskList
taskList :: TaskList
domain :: Text
reverseOrder :: Maybe Bool
nextPageToken :: Maybe Text
maximumPageSize :: Maybe Natural
identity :: Maybe Text
$sel:taskList:PollForDecisionTask' :: PollForDecisionTask -> TaskList
$sel:domain:PollForDecisionTask' :: PollForDecisionTask -> Text
$sel:reverseOrder:PollForDecisionTask' :: PollForDecisionTask -> Maybe Bool
$sel:nextPageToken:PollForDecisionTask' :: PollForDecisionTask -> Maybe Text
$sel:maximumPageSize:PollForDecisionTask' :: PollForDecisionTask -> Maybe Natural
$sel:identity:PollForDecisionTask' :: PollForDecisionTask -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"identity" 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
identity,
            (Key
"maximumPageSize" 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 Natural
maximumPageSize,
            (Key
"nextPageToken" 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
nextPageToken,
            (Key
"reverseOrder" 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 Bool
reverseOrder,
            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
"taskList" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= TaskList
taskList)
          ]
      )

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

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

-- | A structure that represents a decision task. Decision tasks are sent to
-- deciders in order for them to make decisions.
--
-- /See:/ 'newPollForDecisionTaskResponse' smart constructor.
data PollForDecisionTaskResponse = PollForDecisionTaskResponse'
  { -- | A paginated list of history events of the workflow execution. The
    -- decider uses this during the processing of the decision task.
    PollForDecisionTaskResponse -> Maybe [HistoryEvent]
events :: Prelude.Maybe [HistoryEvent],
    -- | If a @NextPageToken@ was returned by a previous call, there are more
    -- results available. To retrieve the next page of results, make the call
    -- again using the returned token in @nextPageToken@. Keep all other
    -- arguments unchanged.
    --
    -- The configured @maximumPageSize@ determines how many results can be
    -- returned in a single call.
    PollForDecisionTaskResponse -> Maybe Text
nextPageToken :: Prelude.Maybe Prelude.Text,
    -- | The ID of the DecisionTaskStarted event of the previous decision task of
    -- this workflow execution that was processed by the decider. This can be
    -- used to determine the events in the history new since the last decision
    -- task received by the decider.
    PollForDecisionTaskResponse -> Maybe Integer
previousStartedEventId :: Prelude.Maybe Prelude.Integer,
    -- | The opaque string used as a handle on the task. This token is used by
    -- workers to communicate progress and response information back to the
    -- system about the task.
    PollForDecisionTaskResponse -> Maybe Text
taskToken :: Prelude.Maybe Prelude.Text,
    -- | The workflow execution for which this decision task was created.
    PollForDecisionTaskResponse -> Maybe WorkflowExecution
workflowExecution :: Prelude.Maybe WorkflowExecution,
    -- | The type of the workflow execution for which this decision task was
    -- created.
    PollForDecisionTaskResponse -> Maybe WorkflowType
workflowType :: Prelude.Maybe WorkflowType,
    -- | The response's http status code.
    PollForDecisionTaskResponse -> Int
httpStatus :: Prelude.Int,
    -- | The ID of the @DecisionTaskStarted@ event recorded in the history.
    PollForDecisionTaskResponse -> Integer
startedEventId :: Prelude.Integer
  }
  deriving (PollForDecisionTaskResponse -> PollForDecisionTaskResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PollForDecisionTaskResponse -> PollForDecisionTaskResponse -> Bool
$c/= :: PollForDecisionTaskResponse -> PollForDecisionTaskResponse -> Bool
== :: PollForDecisionTaskResponse -> PollForDecisionTaskResponse -> Bool
$c== :: PollForDecisionTaskResponse -> PollForDecisionTaskResponse -> Bool
Prelude.Eq, ReadPrec [PollForDecisionTaskResponse]
ReadPrec PollForDecisionTaskResponse
Int -> ReadS PollForDecisionTaskResponse
ReadS [PollForDecisionTaskResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PollForDecisionTaskResponse]
$creadListPrec :: ReadPrec [PollForDecisionTaskResponse]
readPrec :: ReadPrec PollForDecisionTaskResponse
$creadPrec :: ReadPrec PollForDecisionTaskResponse
readList :: ReadS [PollForDecisionTaskResponse]
$creadList :: ReadS [PollForDecisionTaskResponse]
readsPrec :: Int -> ReadS PollForDecisionTaskResponse
$creadsPrec :: Int -> ReadS PollForDecisionTaskResponse
Prelude.Read, Int -> PollForDecisionTaskResponse -> ShowS
[PollForDecisionTaskResponse] -> ShowS
PollForDecisionTaskResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PollForDecisionTaskResponse] -> ShowS
$cshowList :: [PollForDecisionTaskResponse] -> ShowS
show :: PollForDecisionTaskResponse -> String
$cshow :: PollForDecisionTaskResponse -> String
showsPrec :: Int -> PollForDecisionTaskResponse -> ShowS
$cshowsPrec :: Int -> PollForDecisionTaskResponse -> ShowS
Prelude.Show, forall x.
Rep PollForDecisionTaskResponse x -> PollForDecisionTaskResponse
forall x.
PollForDecisionTaskResponse -> Rep PollForDecisionTaskResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PollForDecisionTaskResponse x -> PollForDecisionTaskResponse
$cfrom :: forall x.
PollForDecisionTaskResponse -> Rep PollForDecisionTaskResponse x
Prelude.Generic)

-- |
-- Create a value of 'PollForDecisionTaskResponse' 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:
--
-- 'events', 'pollForDecisionTaskResponse_events' - A paginated list of history events of the workflow execution. The
-- decider uses this during the processing of the decision task.
--
-- 'nextPageToken', 'pollForDecisionTaskResponse_nextPageToken' - If a @NextPageToken@ was returned by a previous call, there are more
-- results available. To retrieve the next page of results, make the call
-- again using the returned token in @nextPageToken@. Keep all other
-- arguments unchanged.
--
-- The configured @maximumPageSize@ determines how many results can be
-- returned in a single call.
--
-- 'previousStartedEventId', 'pollForDecisionTaskResponse_previousStartedEventId' - The ID of the DecisionTaskStarted event of the previous decision task of
-- this workflow execution that was processed by the decider. This can be
-- used to determine the events in the history new since the last decision
-- task received by the decider.
--
-- 'taskToken', 'pollForDecisionTaskResponse_taskToken' - The opaque string used as a handle on the task. This token is used by
-- workers to communicate progress and response information back to the
-- system about the task.
--
-- 'workflowExecution', 'pollForDecisionTaskResponse_workflowExecution' - The workflow execution for which this decision task was created.
--
-- 'workflowType', 'pollForDecisionTaskResponse_workflowType' - The type of the workflow execution for which this decision task was
-- created.
--
-- 'httpStatus', 'pollForDecisionTaskResponse_httpStatus' - The response's http status code.
--
-- 'startedEventId', 'pollForDecisionTaskResponse_startedEventId' - The ID of the @DecisionTaskStarted@ event recorded in the history.
newPollForDecisionTaskResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'startedEventId'
  Prelude.Integer ->
  PollForDecisionTaskResponse
newPollForDecisionTaskResponse :: Int -> Integer -> PollForDecisionTaskResponse
newPollForDecisionTaskResponse
  Int
pHttpStatus_
  Integer
pStartedEventId_ =
    PollForDecisionTaskResponse'
      { $sel:events:PollForDecisionTaskResponse' :: Maybe [HistoryEvent]
events =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nextPageToken:PollForDecisionTaskResponse' :: Maybe Text
nextPageToken = forall a. Maybe a
Prelude.Nothing,
        $sel:previousStartedEventId:PollForDecisionTaskResponse' :: Maybe Integer
previousStartedEventId = forall a. Maybe a
Prelude.Nothing,
        $sel:taskToken:PollForDecisionTaskResponse' :: Maybe Text
taskToken = forall a. Maybe a
Prelude.Nothing,
        $sel:workflowExecution:PollForDecisionTaskResponse' :: Maybe WorkflowExecution
workflowExecution = forall a. Maybe a
Prelude.Nothing,
        $sel:workflowType:PollForDecisionTaskResponse' :: Maybe WorkflowType
workflowType = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:PollForDecisionTaskResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:startedEventId:PollForDecisionTaskResponse' :: Integer
startedEventId = Integer
pStartedEventId_
      }

-- | A paginated list of history events of the workflow execution. The
-- decider uses this during the processing of the decision task.
pollForDecisionTaskResponse_events :: Lens.Lens' PollForDecisionTaskResponse (Prelude.Maybe [HistoryEvent])
pollForDecisionTaskResponse_events :: Lens' PollForDecisionTaskResponse (Maybe [HistoryEvent])
pollForDecisionTaskResponse_events = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PollForDecisionTaskResponse' {Maybe [HistoryEvent]
events :: Maybe [HistoryEvent]
$sel:events:PollForDecisionTaskResponse' :: PollForDecisionTaskResponse -> Maybe [HistoryEvent]
events} -> Maybe [HistoryEvent]
events) (\s :: PollForDecisionTaskResponse
s@PollForDecisionTaskResponse' {} Maybe [HistoryEvent]
a -> PollForDecisionTaskResponse
s {$sel:events:PollForDecisionTaskResponse' :: Maybe [HistoryEvent]
events = Maybe [HistoryEvent]
a} :: PollForDecisionTaskResponse) 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

-- | If a @NextPageToken@ was returned by a previous call, there are more
-- results available. To retrieve the next page of results, make the call
-- again using the returned token in @nextPageToken@. Keep all other
-- arguments unchanged.
--
-- The configured @maximumPageSize@ determines how many results can be
-- returned in a single call.
pollForDecisionTaskResponse_nextPageToken :: Lens.Lens' PollForDecisionTaskResponse (Prelude.Maybe Prelude.Text)
pollForDecisionTaskResponse_nextPageToken :: Lens' PollForDecisionTaskResponse (Maybe Text)
pollForDecisionTaskResponse_nextPageToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PollForDecisionTaskResponse' {Maybe Text
nextPageToken :: Maybe Text
$sel:nextPageToken:PollForDecisionTaskResponse' :: PollForDecisionTaskResponse -> Maybe Text
nextPageToken} -> Maybe Text
nextPageToken) (\s :: PollForDecisionTaskResponse
s@PollForDecisionTaskResponse' {} Maybe Text
a -> PollForDecisionTaskResponse
s {$sel:nextPageToken:PollForDecisionTaskResponse' :: Maybe Text
nextPageToken = Maybe Text
a} :: PollForDecisionTaskResponse)

-- | The ID of the DecisionTaskStarted event of the previous decision task of
-- this workflow execution that was processed by the decider. This can be
-- used to determine the events in the history new since the last decision
-- task received by the decider.
pollForDecisionTaskResponse_previousStartedEventId :: Lens.Lens' PollForDecisionTaskResponse (Prelude.Maybe Prelude.Integer)
pollForDecisionTaskResponse_previousStartedEventId :: Lens' PollForDecisionTaskResponse (Maybe Integer)
pollForDecisionTaskResponse_previousStartedEventId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PollForDecisionTaskResponse' {Maybe Integer
previousStartedEventId :: Maybe Integer
$sel:previousStartedEventId:PollForDecisionTaskResponse' :: PollForDecisionTaskResponse -> Maybe Integer
previousStartedEventId} -> Maybe Integer
previousStartedEventId) (\s :: PollForDecisionTaskResponse
s@PollForDecisionTaskResponse' {} Maybe Integer
a -> PollForDecisionTaskResponse
s {$sel:previousStartedEventId:PollForDecisionTaskResponse' :: Maybe Integer
previousStartedEventId = Maybe Integer
a} :: PollForDecisionTaskResponse)

-- | The opaque string used as a handle on the task. This token is used by
-- workers to communicate progress and response information back to the
-- system about the task.
pollForDecisionTaskResponse_taskToken :: Lens.Lens' PollForDecisionTaskResponse (Prelude.Maybe Prelude.Text)
pollForDecisionTaskResponse_taskToken :: Lens' PollForDecisionTaskResponse (Maybe Text)
pollForDecisionTaskResponse_taskToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PollForDecisionTaskResponse' {Maybe Text
taskToken :: Maybe Text
$sel:taskToken:PollForDecisionTaskResponse' :: PollForDecisionTaskResponse -> Maybe Text
taskToken} -> Maybe Text
taskToken) (\s :: PollForDecisionTaskResponse
s@PollForDecisionTaskResponse' {} Maybe Text
a -> PollForDecisionTaskResponse
s {$sel:taskToken:PollForDecisionTaskResponse' :: Maybe Text
taskToken = Maybe Text
a} :: PollForDecisionTaskResponse)

-- | The workflow execution for which this decision task was created.
pollForDecisionTaskResponse_workflowExecution :: Lens.Lens' PollForDecisionTaskResponse (Prelude.Maybe WorkflowExecution)
pollForDecisionTaskResponse_workflowExecution :: Lens' PollForDecisionTaskResponse (Maybe WorkflowExecution)
pollForDecisionTaskResponse_workflowExecution = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PollForDecisionTaskResponse' {Maybe WorkflowExecution
workflowExecution :: Maybe WorkflowExecution
$sel:workflowExecution:PollForDecisionTaskResponse' :: PollForDecisionTaskResponse -> Maybe WorkflowExecution
workflowExecution} -> Maybe WorkflowExecution
workflowExecution) (\s :: PollForDecisionTaskResponse
s@PollForDecisionTaskResponse' {} Maybe WorkflowExecution
a -> PollForDecisionTaskResponse
s {$sel:workflowExecution:PollForDecisionTaskResponse' :: Maybe WorkflowExecution
workflowExecution = Maybe WorkflowExecution
a} :: PollForDecisionTaskResponse)

-- | The type of the workflow execution for which this decision task was
-- created.
pollForDecisionTaskResponse_workflowType :: Lens.Lens' PollForDecisionTaskResponse (Prelude.Maybe WorkflowType)
pollForDecisionTaskResponse_workflowType :: Lens' PollForDecisionTaskResponse (Maybe WorkflowType)
pollForDecisionTaskResponse_workflowType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PollForDecisionTaskResponse' {Maybe WorkflowType
workflowType :: Maybe WorkflowType
$sel:workflowType:PollForDecisionTaskResponse' :: PollForDecisionTaskResponse -> Maybe WorkflowType
workflowType} -> Maybe WorkflowType
workflowType) (\s :: PollForDecisionTaskResponse
s@PollForDecisionTaskResponse' {} Maybe WorkflowType
a -> PollForDecisionTaskResponse
s {$sel:workflowType:PollForDecisionTaskResponse' :: Maybe WorkflowType
workflowType = Maybe WorkflowType
a} :: PollForDecisionTaskResponse)

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

-- | The ID of the @DecisionTaskStarted@ event recorded in the history.
pollForDecisionTaskResponse_startedEventId :: Lens.Lens' PollForDecisionTaskResponse Prelude.Integer
pollForDecisionTaskResponse_startedEventId :: Lens' PollForDecisionTaskResponse Integer
pollForDecisionTaskResponse_startedEventId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PollForDecisionTaskResponse' {Integer
startedEventId :: Integer
$sel:startedEventId:PollForDecisionTaskResponse' :: PollForDecisionTaskResponse -> Integer
startedEventId} -> Integer
startedEventId) (\s :: PollForDecisionTaskResponse
s@PollForDecisionTaskResponse' {} Integer
a -> PollForDecisionTaskResponse
s {$sel:startedEventId:PollForDecisionTaskResponse' :: Integer
startedEventId = Integer
a} :: PollForDecisionTaskResponse)

instance Prelude.NFData PollForDecisionTaskResponse where
  rnf :: PollForDecisionTaskResponse -> ()
rnf PollForDecisionTaskResponse' {Int
Integer
Maybe Integer
Maybe [HistoryEvent]
Maybe Text
Maybe WorkflowExecution
Maybe WorkflowType
startedEventId :: Integer
httpStatus :: Int
workflowType :: Maybe WorkflowType
workflowExecution :: Maybe WorkflowExecution
taskToken :: Maybe Text
previousStartedEventId :: Maybe Integer
nextPageToken :: Maybe Text
events :: Maybe [HistoryEvent]
$sel:startedEventId:PollForDecisionTaskResponse' :: PollForDecisionTaskResponse -> Integer
$sel:httpStatus:PollForDecisionTaskResponse' :: PollForDecisionTaskResponse -> Int
$sel:workflowType:PollForDecisionTaskResponse' :: PollForDecisionTaskResponse -> Maybe WorkflowType
$sel:workflowExecution:PollForDecisionTaskResponse' :: PollForDecisionTaskResponse -> Maybe WorkflowExecution
$sel:taskToken:PollForDecisionTaskResponse' :: PollForDecisionTaskResponse -> Maybe Text
$sel:previousStartedEventId:PollForDecisionTaskResponse' :: PollForDecisionTaskResponse -> Maybe Integer
$sel:nextPageToken:PollForDecisionTaskResponse' :: PollForDecisionTaskResponse -> Maybe Text
$sel:events:PollForDecisionTaskResponse' :: PollForDecisionTaskResponse -> Maybe [HistoryEvent]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [HistoryEvent]
events
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextPageToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
previousStartedEventId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
taskToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe WorkflowExecution
workflowExecution
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe WorkflowType
workflowType
      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 Integer
startedEventId