{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveLift #-}
{-# LANGUAGE DuplicateRecordFields #-}
module Temporal.Workflow.Types where
import Data.Data (Data)
import Data.Map.Strict (Map)
import Data.Text (Text)
import Data.Time.Clock.System (SystemTime)
import Data.Vector (Vector)
import Data.Word (Word32)
import Language.Haskell.TH.Syntax (Lift)
import qualified Proto.Temporal.Sdk.Core.ChildWorkflow.ChildWorkflow as ChildWorkflow
import Temporal.Activity.Types
import Temporal.Common
import Temporal.Common.TimeoutType
import Temporal.Duration
import Temporal.Payload
import Temporal.SearchAttributes
data Info = Info
{ Info -> Word32
historyLength :: {-# UNPACK #-} !Word32
, Info -> Int
attempt :: {-# UNPACK #-} !Int
, Info -> Maybe RunId
continuedRunId :: !(Maybe RunId)
, Info -> Maybe Text
cronSchedule :: !(Maybe Text)
, Info -> Maybe Duration
executionTimeout :: !(Maybe Duration)
, :: !(Map Text Payload)
, Info -> Namespace
namespace :: !Namespace
, Info -> Maybe ParentInfo
parent :: !(Maybe ParentInfo)
, Info -> Map Text Payload
rawMemo :: !(Map Text Payload)
, Info -> Maybe RetryPolicy
retryPolicy :: !(Maybe RetryPolicy)
, Info -> RunId
runId :: !RunId
, Info -> Maybe Duration
runTimeout :: !(Maybe Duration)
, Info -> Map SearchAttributeKey SearchAttributeType
searchAttributes :: !(Map SearchAttributeKey SearchAttributeType)
, Info -> SystemTime
startTime :: !SystemTime
, Info -> TaskQueue
taskQueue :: !TaskQueue
, Info -> Duration
taskTimeout :: !Duration
, Info -> WorkflowId
workflowId :: !WorkflowId
, Info -> WorkflowType
workflowType :: !WorkflowType
, Info -> Bool
continueAsNewSuggested :: !Bool
}
deriving stock (Int -> Info -> ShowS
[Info] -> ShowS
Info -> String
(Int -> Info -> ShowS)
-> (Info -> String) -> ([Info] -> ShowS) -> Show Info
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Info -> ShowS
showsPrec :: Int -> Info -> ShowS
$cshow :: Info -> String
show :: Info -> String
$cshowList :: [Info] -> ShowS
showList :: [Info] -> ShowS
Show)
data ActivityTimeoutPolicy
= StartToCloseTimeout !Duration
| ScheduleToCloseTimeout !Duration
| StartToCloseAndScheduleToCloseTimeout !Duration !Duration
deriving stock (ActivityTimeoutPolicy -> ActivityTimeoutPolicy -> Bool
(ActivityTimeoutPolicy -> ActivityTimeoutPolicy -> Bool)
-> (ActivityTimeoutPolicy -> ActivityTimeoutPolicy -> Bool)
-> Eq ActivityTimeoutPolicy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ActivityTimeoutPolicy -> ActivityTimeoutPolicy -> Bool
== :: ActivityTimeoutPolicy -> ActivityTimeoutPolicy -> Bool
$c/= :: ActivityTimeoutPolicy -> ActivityTimeoutPolicy -> Bool
/= :: ActivityTimeoutPolicy -> ActivityTimeoutPolicy -> Bool
Eq, Int -> ActivityTimeoutPolicy -> ShowS
[ActivityTimeoutPolicy] -> ShowS
ActivityTimeoutPolicy -> String
(Int -> ActivityTimeoutPolicy -> ShowS)
-> (ActivityTimeoutPolicy -> String)
-> ([ActivityTimeoutPolicy] -> ShowS)
-> Show ActivityTimeoutPolicy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ActivityTimeoutPolicy -> ShowS
showsPrec :: Int -> ActivityTimeoutPolicy -> ShowS
$cshow :: ActivityTimeoutPolicy -> String
show :: ActivityTimeoutPolicy -> String
$cshowList :: [ActivityTimeoutPolicy] -> ShowS
showList :: [ActivityTimeoutPolicy] -> ShowS
Show, Typeable ActivityTimeoutPolicy
Typeable ActivityTimeoutPolicy =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ActivityTimeoutPolicy
-> c ActivityTimeoutPolicy)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ActivityTimeoutPolicy)
-> (ActivityTimeoutPolicy -> Constr)
-> (ActivityTimeoutPolicy -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ActivityTimeoutPolicy))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ActivityTimeoutPolicy))
-> ((forall b. Data b => b -> b)
-> ActivityTimeoutPolicy -> ActivityTimeoutPolicy)
-> (forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ActivityTimeoutPolicy
-> r)
-> (forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ActivityTimeoutPolicy
-> r)
-> (forall u.
(forall d. Data d => d -> u) -> ActivityTimeoutPolicy -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ActivityTimeoutPolicy -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ActivityTimeoutPolicy -> m ActivityTimeoutPolicy)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ActivityTimeoutPolicy -> m ActivityTimeoutPolicy)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ActivityTimeoutPolicy -> m ActivityTimeoutPolicy)
-> Data ActivityTimeoutPolicy
ActivityTimeoutPolicy -> Constr
ActivityTimeoutPolicy -> DataType
(forall b. Data b => b -> b)
-> ActivityTimeoutPolicy -> ActivityTimeoutPolicy
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> ActivityTimeoutPolicy -> u
forall u.
(forall d. Data d => d -> u) -> ActivityTimeoutPolicy -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ActivityTimeoutPolicy -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ActivityTimeoutPolicy -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ActivityTimeoutPolicy -> m ActivityTimeoutPolicy
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ActivityTimeoutPolicy -> m ActivityTimeoutPolicy
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ActivityTimeoutPolicy
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ActivityTimeoutPolicy
-> c ActivityTimeoutPolicy
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ActivityTimeoutPolicy)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ActivityTimeoutPolicy)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ActivityTimeoutPolicy
-> c ActivityTimeoutPolicy
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ActivityTimeoutPolicy
-> c ActivityTimeoutPolicy
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ActivityTimeoutPolicy
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ActivityTimeoutPolicy
$ctoConstr :: ActivityTimeoutPolicy -> Constr
toConstr :: ActivityTimeoutPolicy -> Constr
$cdataTypeOf :: ActivityTimeoutPolicy -> DataType
dataTypeOf :: ActivityTimeoutPolicy -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ActivityTimeoutPolicy)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ActivityTimeoutPolicy)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ActivityTimeoutPolicy)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ActivityTimeoutPolicy)
$cgmapT :: (forall b. Data b => b -> b)
-> ActivityTimeoutPolicy -> ActivityTimeoutPolicy
gmapT :: (forall b. Data b => b -> b)
-> ActivityTimeoutPolicy -> ActivityTimeoutPolicy
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ActivityTimeoutPolicy -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ActivityTimeoutPolicy -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ActivityTimeoutPolicy -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ActivityTimeoutPolicy -> r
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> ActivityTimeoutPolicy -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> ActivityTimeoutPolicy -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ActivityTimeoutPolicy -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ActivityTimeoutPolicy -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ActivityTimeoutPolicy -> m ActivityTimeoutPolicy
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ActivityTimeoutPolicy -> m ActivityTimeoutPolicy
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ActivityTimeoutPolicy -> m ActivityTimeoutPolicy
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ActivityTimeoutPolicy -> m ActivityTimeoutPolicy
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ActivityTimeoutPolicy -> m ActivityTimeoutPolicy
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ActivityTimeoutPolicy -> m ActivityTimeoutPolicy
Data, (forall (m :: * -> *). Quote m => ActivityTimeoutPolicy -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
ActivityTimeoutPolicy -> Code m ActivityTimeoutPolicy)
-> Lift ActivityTimeoutPolicy
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => ActivityTimeoutPolicy -> m Exp
forall (m :: * -> *).
Quote m =>
ActivityTimeoutPolicy -> Code m ActivityTimeoutPolicy
$clift :: forall (m :: * -> *). Quote m => ActivityTimeoutPolicy -> m Exp
lift :: forall (m :: * -> *). Quote m => ActivityTimeoutPolicy -> m Exp
$cliftTyped :: forall (m :: * -> *).
Quote m =>
ActivityTimeoutPolicy -> Code m ActivityTimeoutPolicy
liftTyped :: forall (m :: * -> *).
Quote m =>
ActivityTimeoutPolicy -> Code m ActivityTimeoutPolicy
Lift)
data StartActivityOptions = StartActivityOptions
{ StartActivityOptions -> Maybe ActivityId
activityId :: Maybe ActivityId
, StartActivityOptions -> Maybe TaskQueue
taskQueue :: Maybe TaskQueue
, StartActivityOptions -> ActivityTimeoutPolicy
timeout :: ActivityTimeoutPolicy
, StartActivityOptions -> Maybe Duration
scheduleToStartTimeout :: Maybe Duration
, StartActivityOptions -> Maybe Duration
heartbeatTimeout :: Maybe Duration
, StartActivityOptions -> Maybe RetryPolicy
retryPolicy :: Maybe RetryPolicy
, StartActivityOptions -> ActivityCancellationType
cancellationType :: ActivityCancellationType
, :: Map Text Payload
, StartActivityOptions -> Bool
disableEagerExecution :: Bool
}
deriving stock (Int -> StartActivityOptions -> ShowS
[StartActivityOptions] -> ShowS
StartActivityOptions -> String
(Int -> StartActivityOptions -> ShowS)
-> (StartActivityOptions -> String)
-> ([StartActivityOptions] -> ShowS)
-> Show StartActivityOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StartActivityOptions -> ShowS
showsPrec :: Int -> StartActivityOptions -> ShowS
$cshow :: StartActivityOptions -> String
show :: StartActivityOptions -> String
$cshowList :: [StartActivityOptions] -> ShowS
showList :: [StartActivityOptions] -> ShowS
Show, (forall (m :: * -> *). Quote m => StartActivityOptions -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
StartActivityOptions -> Code m StartActivityOptions)
-> Lift StartActivityOptions
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => StartActivityOptions -> m Exp
forall (m :: * -> *).
Quote m =>
StartActivityOptions -> Code m StartActivityOptions
$clift :: forall (m :: * -> *). Quote m => StartActivityOptions -> m Exp
lift :: forall (m :: * -> *). Quote m => StartActivityOptions -> m Exp
$cliftTyped :: forall (m :: * -> *).
Quote m =>
StartActivityOptions -> Code m StartActivityOptions
liftTyped :: forall (m :: * -> *).
Quote m =>
StartActivityOptions -> Code m StartActivityOptions
Lift)
class StartActivityTimeoutOption a where
toStartActivityTimeoutOption :: a -> ActivityTimeoutPolicy
instance StartActivityTimeoutOption ActivityTimeoutPolicy where
toStartActivityTimeoutOption :: ActivityTimeoutPolicy -> ActivityTimeoutPolicy
toStartActivityTimeoutOption = ActivityTimeoutPolicy -> ActivityTimeoutPolicy
forall a. a -> a
id
instance StartActivityTimeoutOption StartToClose where
toStartActivityTimeoutOption :: StartToClose -> ActivityTimeoutPolicy
toStartActivityTimeoutOption (StartToClose Duration
t) = Duration -> ActivityTimeoutPolicy
StartToCloseTimeout Duration
t
instance StartActivityTimeoutOption ScheduleToClose where
toStartActivityTimeoutOption :: ScheduleToClose -> ActivityTimeoutPolicy
toStartActivityTimeoutOption (ScheduleToClose Duration
t) = Duration -> ActivityTimeoutPolicy
ScheduleToCloseTimeout Duration
t
instance StartActivityTimeoutOption (StartToClose, ScheduleToClose) where
toStartActivityTimeoutOption :: (StartToClose, ScheduleToClose) -> ActivityTimeoutPolicy
toStartActivityTimeoutOption (StartToClose Duration
s, ScheduleToClose Duration
sc) = Duration -> Duration -> ActivityTimeoutPolicy
StartToCloseAndScheduleToCloseTimeout Duration
s Duration
sc
instance StartActivityTimeoutOption (ScheduleToClose, StartToClose) where
toStartActivityTimeoutOption :: (ScheduleToClose, StartToClose) -> ActivityTimeoutPolicy
toStartActivityTimeoutOption (ScheduleToClose Duration
sc, StartToClose Duration
s) = Duration -> Duration -> ActivityTimeoutPolicy
StartToCloseAndScheduleToCloseTimeout Duration
s Duration
sc
instance StartActivityTimeoutOption (Either StartToClose ScheduleToClose) where
toStartActivityTimeoutOption :: Either StartToClose ScheduleToClose -> ActivityTimeoutPolicy
toStartActivityTimeoutOption = (StartToClose -> ActivityTimeoutPolicy)
-> (ScheduleToClose -> ActivityTimeoutPolicy)
-> Either StartToClose ScheduleToClose
-> ActivityTimeoutPolicy
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either StartToClose -> ActivityTimeoutPolicy
forall a.
StartActivityTimeoutOption a =>
a -> ActivityTimeoutPolicy
toStartActivityTimeoutOption ScheduleToClose -> ActivityTimeoutPolicy
forall a.
StartActivityTimeoutOption a =>
a -> ActivityTimeoutPolicy
toStartActivityTimeoutOption
instance StartActivityTimeoutOption (Either ScheduleToClose StartToClose) where
toStartActivityTimeoutOption :: Either ScheduleToClose StartToClose -> ActivityTimeoutPolicy
toStartActivityTimeoutOption = (ScheduleToClose -> ActivityTimeoutPolicy)
-> (StartToClose -> ActivityTimeoutPolicy)
-> Either ScheduleToClose StartToClose
-> ActivityTimeoutPolicy
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ScheduleToClose -> ActivityTimeoutPolicy
forall a.
StartActivityTimeoutOption a =>
a -> ActivityTimeoutPolicy
toStartActivityTimeoutOption StartToClose -> ActivityTimeoutPolicy
forall a.
StartActivityTimeoutOption a =>
a -> ActivityTimeoutPolicy
toStartActivityTimeoutOption
defaultStartActivityOptions :: StartActivityTimeoutOption timeout => timeout -> StartActivityOptions
defaultStartActivityOptions :: forall timeout.
StartActivityTimeoutOption timeout =>
timeout -> StartActivityOptions
defaultStartActivityOptions timeout
t =
StartActivityOptions
{ activityId :: Maybe ActivityId
activityId = Maybe ActivityId
forall a. Maybe a
Nothing
, taskQueue :: Maybe TaskQueue
taskQueue = Maybe TaskQueue
forall a. Maybe a
Nothing
, timeout :: ActivityTimeoutPolicy
timeout = timeout -> ActivityTimeoutPolicy
forall a.
StartActivityTimeoutOption a =>
a -> ActivityTimeoutPolicy
toStartActivityTimeoutOption timeout
t
, scheduleToStartTimeout :: Maybe Duration
scheduleToStartTimeout = Maybe Duration
forall a. Maybe a
Nothing
, heartbeatTimeout :: Maybe Duration
heartbeatTimeout = Maybe Duration
forall a. Maybe a
Nothing
, retryPolicy :: Maybe RetryPolicy
retryPolicy = Maybe RetryPolicy
forall a. Maybe a
Nothing
, cancellationType :: ActivityCancellationType
cancellationType = ActivityCancellationType
ActivityCancellationTryCancel
, headers :: Map Text Payload
headers = Map Text Payload
forall a. Monoid a => a
mempty
, disableEagerExecution :: Bool
disableEagerExecution = Bool
False
}
data ActivityCancellationType
=
ActivityCancellationTryCancel
|
ActivityCancellationWaitCancellationCompleted
|
ActivityCancellationAbandon
deriving stock (Int -> ActivityCancellationType -> ShowS
[ActivityCancellationType] -> ShowS
ActivityCancellationType -> String
(Int -> ActivityCancellationType -> ShowS)
-> (ActivityCancellationType -> String)
-> ([ActivityCancellationType] -> ShowS)
-> Show ActivityCancellationType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ActivityCancellationType -> ShowS
showsPrec :: Int -> ActivityCancellationType -> ShowS
$cshow :: ActivityCancellationType -> String
show :: ActivityCancellationType -> String
$cshowList :: [ActivityCancellationType] -> ShowS
showList :: [ActivityCancellationType] -> ShowS
Show, ActivityCancellationType -> ActivityCancellationType -> Bool
(ActivityCancellationType -> ActivityCancellationType -> Bool)
-> (ActivityCancellationType -> ActivityCancellationType -> Bool)
-> Eq ActivityCancellationType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ActivityCancellationType -> ActivityCancellationType -> Bool
== :: ActivityCancellationType -> ActivityCancellationType -> Bool
$c/= :: ActivityCancellationType -> ActivityCancellationType -> Bool
/= :: ActivityCancellationType -> ActivityCancellationType -> Bool
Eq, (forall (m :: * -> *).
Quote m =>
ActivityCancellationType -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
ActivityCancellationType -> Code m ActivityCancellationType)
-> Lift ActivityCancellationType
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => ActivityCancellationType -> m Exp
forall (m :: * -> *).
Quote m =>
ActivityCancellationType -> Code m ActivityCancellationType
$clift :: forall (m :: * -> *). Quote m => ActivityCancellationType -> m Exp
lift :: forall (m :: * -> *). Quote m => ActivityCancellationType -> m Exp
$cliftTyped :: forall (m :: * -> *).
Quote m =>
ActivityCancellationType -> Code m ActivityCancellationType
liftTyped :: forall (m :: * -> *).
Quote m =>
ActivityCancellationType -> Code m ActivityCancellationType
Lift, Typeable ActivityCancellationType
Typeable ActivityCancellationType =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ActivityCancellationType
-> c ActivityCancellationType)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ActivityCancellationType)
-> (ActivityCancellationType -> Constr)
-> (ActivityCancellationType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c ActivityCancellationType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ActivityCancellationType))
-> ((forall b. Data b => b -> b)
-> ActivityCancellationType -> ActivityCancellationType)
-> (forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ActivityCancellationType
-> r)
-> (forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ActivityCancellationType
-> r)
-> (forall u.
(forall d. Data d => d -> u) -> ActivityCancellationType -> [u])
-> (forall u.
Int
-> (forall d. Data d => d -> u) -> ActivityCancellationType -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ActivityCancellationType -> m ActivityCancellationType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ActivityCancellationType -> m ActivityCancellationType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ActivityCancellationType -> m ActivityCancellationType)
-> Data ActivityCancellationType
ActivityCancellationType -> Constr
ActivityCancellationType -> DataType
(forall b. Data b => b -> b)
-> ActivityCancellationType -> ActivityCancellationType
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int
-> (forall d. Data d => d -> u) -> ActivityCancellationType -> u
forall u.
(forall d. Data d => d -> u) -> ActivityCancellationType -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ActivityCancellationType
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ActivityCancellationType
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ActivityCancellationType -> m ActivityCancellationType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ActivityCancellationType -> m ActivityCancellationType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ActivityCancellationType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ActivityCancellationType
-> c ActivityCancellationType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ActivityCancellationType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ActivityCancellationType)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ActivityCancellationType
-> c ActivityCancellationType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ActivityCancellationType
-> c ActivityCancellationType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ActivityCancellationType
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ActivityCancellationType
$ctoConstr :: ActivityCancellationType -> Constr
toConstr :: ActivityCancellationType -> Constr
$cdataTypeOf :: ActivityCancellationType -> DataType
dataTypeOf :: ActivityCancellationType -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ActivityCancellationType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ActivityCancellationType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ActivityCancellationType)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ActivityCancellationType)
$cgmapT :: (forall b. Data b => b -> b)
-> ActivityCancellationType -> ActivityCancellationType
gmapT :: (forall b. Data b => b -> b)
-> ActivityCancellationType -> ActivityCancellationType
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ActivityCancellationType
-> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ActivityCancellationType
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ActivityCancellationType
-> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ActivityCancellationType
-> r
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> ActivityCancellationType -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> ActivityCancellationType -> [u]
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> ActivityCancellationType -> u
gmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> ActivityCancellationType -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ActivityCancellationType -> m ActivityCancellationType
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ActivityCancellationType -> m ActivityCancellationType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ActivityCancellationType -> m ActivityCancellationType
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ActivityCancellationType -> m ActivityCancellationType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ActivityCancellationType -> m ActivityCancellationType
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ActivityCancellationType -> m ActivityCancellationType
Data)
data ExecuteActivityInput = ExecuteActivityInput
{ ExecuteActivityInput -> Vector Payload
activityArgs :: Vector Payload
, :: Map Text Payload
, ExecuteActivityInput -> ActivityInfo
activityInfo :: ActivityInfo
}
deriving stock (Int -> ExecuteActivityInput -> ShowS
[ExecuteActivityInput] -> ShowS
ExecuteActivityInput -> String
(Int -> ExecuteActivityInput -> ShowS)
-> (ExecuteActivityInput -> String)
-> ([ExecuteActivityInput] -> ShowS)
-> Show ExecuteActivityInput
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExecuteActivityInput -> ShowS
showsPrec :: Int -> ExecuteActivityInput -> ShowS
$cshow :: ExecuteActivityInput -> String
show :: ExecuteActivityInput -> String
$cshowList :: [ExecuteActivityInput] -> ShowS
showList :: [ExecuteActivityInput] -> ShowS
Show)
data ChildWorkflowCancellationType
=
ChildWorkflowCancellationAbandon
|
ChildWorkflowCancellationTryCancel
|
ChildWorkflowCancellationWaitCancellationCompleted
|
ChildWorkflowCancellationWaitCancellationRequested
deriving stock (Int -> ChildWorkflowCancellationType -> ShowS
[ChildWorkflowCancellationType] -> ShowS
ChildWorkflowCancellationType -> String
(Int -> ChildWorkflowCancellationType -> ShowS)
-> (ChildWorkflowCancellationType -> String)
-> ([ChildWorkflowCancellationType] -> ShowS)
-> Show ChildWorkflowCancellationType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChildWorkflowCancellationType -> ShowS
showsPrec :: Int -> ChildWorkflowCancellationType -> ShowS
$cshow :: ChildWorkflowCancellationType -> String
show :: ChildWorkflowCancellationType -> String
$cshowList :: [ChildWorkflowCancellationType] -> ShowS
showList :: [ChildWorkflowCancellationType] -> ShowS
Show, ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Bool
(ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Bool)
-> (ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Bool)
-> Eq ChildWorkflowCancellationType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Bool
== :: ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Bool
$c/= :: ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Bool
/= :: ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Bool
Eq, Eq ChildWorkflowCancellationType
Eq ChildWorkflowCancellationType =>
(ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Ordering)
-> (ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Bool)
-> (ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Bool)
-> (ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Bool)
-> (ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Bool)
-> (ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> ChildWorkflowCancellationType)
-> (ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> ChildWorkflowCancellationType)
-> Ord ChildWorkflowCancellationType
ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Bool
ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Ordering
ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> ChildWorkflowCancellationType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Ordering
compare :: ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Ordering
$c< :: ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Bool
< :: ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Bool
$c<= :: ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Bool
<= :: ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Bool
$c> :: ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Bool
> :: ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Bool
$c>= :: ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Bool
>= :: ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> Bool
$cmax :: ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> ChildWorkflowCancellationType
max :: ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> ChildWorkflowCancellationType
$cmin :: ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> ChildWorkflowCancellationType
min :: ChildWorkflowCancellationType
-> ChildWorkflowCancellationType -> ChildWorkflowCancellationType
Ord, (forall (m :: * -> *).
Quote m =>
ChildWorkflowCancellationType -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
ChildWorkflowCancellationType
-> Code m ChildWorkflowCancellationType)
-> Lift ChildWorkflowCancellationType
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *).
Quote m =>
ChildWorkflowCancellationType -> m Exp
forall (m :: * -> *).
Quote m =>
ChildWorkflowCancellationType
-> Code m ChildWorkflowCancellationType
$clift :: forall (m :: * -> *).
Quote m =>
ChildWorkflowCancellationType -> m Exp
lift :: forall (m :: * -> *).
Quote m =>
ChildWorkflowCancellationType -> m Exp
$cliftTyped :: forall (m :: * -> *).
Quote m =>
ChildWorkflowCancellationType
-> Code m ChildWorkflowCancellationType
liftTyped :: forall (m :: * -> *).
Quote m =>
ChildWorkflowCancellationType
-> Code m ChildWorkflowCancellationType
Lift, Typeable ChildWorkflowCancellationType
Typeable ChildWorkflowCancellationType =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ChildWorkflowCancellationType
-> c ChildWorkflowCancellationType)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c ChildWorkflowCancellationType)
-> (ChildWorkflowCancellationType -> Constr)
-> (ChildWorkflowCancellationType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c ChildWorkflowCancellationType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ChildWorkflowCancellationType))
-> ((forall b. Data b => b -> b)
-> ChildWorkflowCancellationType -> ChildWorkflowCancellationType)
-> (forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ChildWorkflowCancellationType
-> r)
-> (forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ChildWorkflowCancellationType
-> r)
-> (forall u.
(forall d. Data d => d -> u)
-> ChildWorkflowCancellationType -> [u])
-> (forall u.
Int
-> (forall d. Data d => d -> u)
-> ChildWorkflowCancellationType
-> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ChildWorkflowCancellationType
-> m ChildWorkflowCancellationType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChildWorkflowCancellationType
-> m ChildWorkflowCancellationType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChildWorkflowCancellationType
-> m ChildWorkflowCancellationType)
-> Data ChildWorkflowCancellationType
ChildWorkflowCancellationType -> Constr
ChildWorkflowCancellationType -> DataType
(forall b. Data b => b -> b)
-> ChildWorkflowCancellationType -> ChildWorkflowCancellationType
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int
-> (forall d. Data d => d -> u)
-> ChildWorkflowCancellationType
-> u
forall u.
(forall d. Data d => d -> u)
-> ChildWorkflowCancellationType -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ChildWorkflowCancellationType
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ChildWorkflowCancellationType
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ChildWorkflowCancellationType -> m ChildWorkflowCancellationType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChildWorkflowCancellationType -> m ChildWorkflowCancellationType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c ChildWorkflowCancellationType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ChildWorkflowCancellationType
-> c ChildWorkflowCancellationType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c ChildWorkflowCancellationType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ChildWorkflowCancellationType)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ChildWorkflowCancellationType
-> c ChildWorkflowCancellationType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ChildWorkflowCancellationType
-> c ChildWorkflowCancellationType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c ChildWorkflowCancellationType
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c ChildWorkflowCancellationType
$ctoConstr :: ChildWorkflowCancellationType -> Constr
toConstr :: ChildWorkflowCancellationType -> Constr
$cdataTypeOf :: ChildWorkflowCancellationType -> DataType
dataTypeOf :: ChildWorkflowCancellationType -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c ChildWorkflowCancellationType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c ChildWorkflowCancellationType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ChildWorkflowCancellationType)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ChildWorkflowCancellationType)
$cgmapT :: (forall b. Data b => b -> b)
-> ChildWorkflowCancellationType -> ChildWorkflowCancellationType
gmapT :: (forall b. Data b => b -> b)
-> ChildWorkflowCancellationType -> ChildWorkflowCancellationType
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ChildWorkflowCancellationType
-> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ChildWorkflowCancellationType
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ChildWorkflowCancellationType
-> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ChildWorkflowCancellationType
-> r
$cgmapQ :: forall u.
(forall d. Data d => d -> u)
-> ChildWorkflowCancellationType -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u)
-> ChildWorkflowCancellationType -> [u]
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u)
-> ChildWorkflowCancellationType
-> u
gmapQi :: forall u.
Int
-> (forall d. Data d => d -> u)
-> ChildWorkflowCancellationType
-> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ChildWorkflowCancellationType -> m ChildWorkflowCancellationType
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ChildWorkflowCancellationType -> m ChildWorkflowCancellationType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChildWorkflowCancellationType -> m ChildWorkflowCancellationType
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChildWorkflowCancellationType -> m ChildWorkflowCancellationType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChildWorkflowCancellationType -> m ChildWorkflowCancellationType
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChildWorkflowCancellationType -> m ChildWorkflowCancellationType
Data)
childWorkflowCancellationTypeToProto :: ChildWorkflowCancellationType -> ChildWorkflow.ChildWorkflowCancellationType
childWorkflowCancellationTypeToProto :: ChildWorkflowCancellationType -> ChildWorkflowCancellationType
childWorkflowCancellationTypeToProto ChildWorkflowCancellationType
ChildWorkflowCancellationAbandon = ChildWorkflowCancellationType
ChildWorkflow.ABANDON
childWorkflowCancellationTypeToProto ChildWorkflowCancellationType
ChildWorkflowCancellationTryCancel = ChildWorkflowCancellationType
ChildWorkflow.TRY_CANCEL
childWorkflowCancellationTypeToProto ChildWorkflowCancellationType
ChildWorkflowCancellationWaitCancellationCompleted = ChildWorkflowCancellationType
ChildWorkflow.WAIT_CANCELLATION_COMPLETED
childWorkflowCancellationTypeToProto ChildWorkflowCancellationType
ChildWorkflowCancellationWaitCancellationRequested = ChildWorkflowCancellationType
ChildWorkflow.WAIT_CANCELLATION_REQUESTED
data ParentClosePolicy
=
ParentClosePolicyUnspecified
|
ParentClosePolicyTerminate
|
ParentClosePolicyAbandon
|
ParentClosePolicyRequestCancel
deriving stock (ParentClosePolicy -> ParentClosePolicy -> Bool
(ParentClosePolicy -> ParentClosePolicy -> Bool)
-> (ParentClosePolicy -> ParentClosePolicy -> Bool)
-> Eq ParentClosePolicy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ParentClosePolicy -> ParentClosePolicy -> Bool
== :: ParentClosePolicy -> ParentClosePolicy -> Bool
$c/= :: ParentClosePolicy -> ParentClosePolicy -> Bool
/= :: ParentClosePolicy -> ParentClosePolicy -> Bool
Eq, Eq ParentClosePolicy
Eq ParentClosePolicy =>
(ParentClosePolicy -> ParentClosePolicy -> Ordering)
-> (ParentClosePolicy -> ParentClosePolicy -> Bool)
-> (ParentClosePolicy -> ParentClosePolicy -> Bool)
-> (ParentClosePolicy -> ParentClosePolicy -> Bool)
-> (ParentClosePolicy -> ParentClosePolicy -> Bool)
-> (ParentClosePolicy -> ParentClosePolicy -> ParentClosePolicy)
-> (ParentClosePolicy -> ParentClosePolicy -> ParentClosePolicy)
-> Ord ParentClosePolicy
ParentClosePolicy -> ParentClosePolicy -> Bool
ParentClosePolicy -> ParentClosePolicy -> Ordering
ParentClosePolicy -> ParentClosePolicy -> ParentClosePolicy
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ParentClosePolicy -> ParentClosePolicy -> Ordering
compare :: ParentClosePolicy -> ParentClosePolicy -> Ordering
$c< :: ParentClosePolicy -> ParentClosePolicy -> Bool
< :: ParentClosePolicy -> ParentClosePolicy -> Bool
$c<= :: ParentClosePolicy -> ParentClosePolicy -> Bool
<= :: ParentClosePolicy -> ParentClosePolicy -> Bool
$c> :: ParentClosePolicy -> ParentClosePolicy -> Bool
> :: ParentClosePolicy -> ParentClosePolicy -> Bool
$c>= :: ParentClosePolicy -> ParentClosePolicy -> Bool
>= :: ParentClosePolicy -> ParentClosePolicy -> Bool
$cmax :: ParentClosePolicy -> ParentClosePolicy -> ParentClosePolicy
max :: ParentClosePolicy -> ParentClosePolicy -> ParentClosePolicy
$cmin :: ParentClosePolicy -> ParentClosePolicy -> ParentClosePolicy
min :: ParentClosePolicy -> ParentClosePolicy -> ParentClosePolicy
Ord, Int -> ParentClosePolicy -> ShowS
[ParentClosePolicy] -> ShowS
ParentClosePolicy -> String
(Int -> ParentClosePolicy -> ShowS)
-> (ParentClosePolicy -> String)
-> ([ParentClosePolicy] -> ShowS)
-> Show ParentClosePolicy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ParentClosePolicy -> ShowS
showsPrec :: Int -> ParentClosePolicy -> ShowS
$cshow :: ParentClosePolicy -> String
show :: ParentClosePolicy -> String
$cshowList :: [ParentClosePolicy] -> ShowS
showList :: [ParentClosePolicy] -> ShowS
Show, (forall (m :: * -> *). Quote m => ParentClosePolicy -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
ParentClosePolicy -> Code m ParentClosePolicy)
-> Lift ParentClosePolicy
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => ParentClosePolicy -> m Exp
forall (m :: * -> *).
Quote m =>
ParentClosePolicy -> Code m ParentClosePolicy
$clift :: forall (m :: * -> *). Quote m => ParentClosePolicy -> m Exp
lift :: forall (m :: * -> *). Quote m => ParentClosePolicy -> m Exp
$cliftTyped :: forall (m :: * -> *).
Quote m =>
ParentClosePolicy -> Code m ParentClosePolicy
liftTyped :: forall (m :: * -> *).
Quote m =>
ParentClosePolicy -> Code m ParentClosePolicy
Lift, Typeable ParentClosePolicy
Typeable ParentClosePolicy =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ParentClosePolicy
-> c ParentClosePolicy)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParentClosePolicy)
-> (ParentClosePolicy -> Constr)
-> (ParentClosePolicy -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ParentClosePolicy))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ParentClosePolicy))
-> ((forall b. Data b => b -> b)
-> ParentClosePolicy -> ParentClosePolicy)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ParentClosePolicy -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParentClosePolicy -> r)
-> (forall u.
(forall d. Data d => d -> u) -> ParentClosePolicy -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ParentClosePolicy -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ParentClosePolicy -> m ParentClosePolicy)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ParentClosePolicy -> m ParentClosePolicy)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ParentClosePolicy -> m ParentClosePolicy)
-> Data ParentClosePolicy
ParentClosePolicy -> Constr
ParentClosePolicy -> DataType
(forall b. Data b => b -> b)
-> ParentClosePolicy -> ParentClosePolicy
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> ParentClosePolicy -> u
forall u. (forall d. Data d => d -> u) -> ParentClosePolicy -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ParentClosePolicy -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParentClosePolicy -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ParentClosePolicy -> m ParentClosePolicy
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ParentClosePolicy -> m ParentClosePolicy
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParentClosePolicy
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParentClosePolicy -> c ParentClosePolicy
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ParentClosePolicy)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ParentClosePolicy)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParentClosePolicy -> c ParentClosePolicy
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParentClosePolicy -> c ParentClosePolicy
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParentClosePolicy
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParentClosePolicy
$ctoConstr :: ParentClosePolicy -> Constr
toConstr :: ParentClosePolicy -> Constr
$cdataTypeOf :: ParentClosePolicy -> DataType
dataTypeOf :: ParentClosePolicy -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ParentClosePolicy)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ParentClosePolicy)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ParentClosePolicy)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ParentClosePolicy)
$cgmapT :: (forall b. Data b => b -> b)
-> ParentClosePolicy -> ParentClosePolicy
gmapT :: (forall b. Data b => b -> b)
-> ParentClosePolicy -> ParentClosePolicy
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ParentClosePolicy -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ParentClosePolicy -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParentClosePolicy -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParentClosePolicy -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ParentClosePolicy -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ParentClosePolicy -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ParentClosePolicy -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ParentClosePolicy -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ParentClosePolicy -> m ParentClosePolicy
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ParentClosePolicy -> m ParentClosePolicy
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ParentClosePolicy -> m ParentClosePolicy
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ParentClosePolicy -> m ParentClosePolicy
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ParentClosePolicy -> m ParentClosePolicy
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ParentClosePolicy -> m ParentClosePolicy
Data)
parentClosePolicyToProto :: ParentClosePolicy -> ChildWorkflow.ParentClosePolicy
parentClosePolicyToProto :: ParentClosePolicy -> ParentClosePolicy
parentClosePolicyToProto ParentClosePolicy
ParentClosePolicyUnspecified = ParentClosePolicy
ChildWorkflow.PARENT_CLOSE_POLICY_UNSPECIFIED
parentClosePolicyToProto ParentClosePolicy
ParentClosePolicyTerminate = ParentClosePolicy
ChildWorkflow.PARENT_CLOSE_POLICY_TERMINATE
parentClosePolicyToProto ParentClosePolicy
ParentClosePolicyAbandon = ParentClosePolicy
ChildWorkflow.PARENT_CLOSE_POLICY_ABANDON
parentClosePolicyToProto ParentClosePolicy
ParentClosePolicyRequestCancel = ParentClosePolicy
ChildWorkflow.PARENT_CLOSE_POLICY_REQUEST_CANCEL
data StartChildWorkflowOptions = StartChildWorkflowOptions
{ StartChildWorkflowOptions -> ChildWorkflowCancellationType
cancellationType :: ChildWorkflowCancellationType
, StartChildWorkflowOptions -> ParentClosePolicy
parentClosePolicy :: ParentClosePolicy
, StartChildWorkflowOptions -> TimeoutOptions
timeoutOptions :: TimeoutOptions
, StartChildWorkflowOptions -> Maybe RetryPolicy
retryPolicy :: Maybe RetryPolicy
, StartChildWorkflowOptions -> Maybe Text
cronSchedule :: Maybe Text
, StartChildWorkflowOptions -> Map Text Payload
initialMemo :: Map Text Payload
, StartChildWorkflowOptions
-> Map SearchAttributeKey SearchAttributeType
searchAttributes :: Map SearchAttributeKey SearchAttributeType
, :: Map Text Payload
, StartChildWorkflowOptions -> WorkflowIdReusePolicy
workflowIdReusePolicy :: WorkflowIdReusePolicy
, StartChildWorkflowOptions -> Maybe WorkflowId
workflowId :: Maybe WorkflowId
, StartChildWorkflowOptions -> Maybe TaskQueue
taskQueue :: Maybe TaskQueue
}
deriving stock (Int -> StartChildWorkflowOptions -> ShowS
[StartChildWorkflowOptions] -> ShowS
StartChildWorkflowOptions -> String
(Int -> StartChildWorkflowOptions -> ShowS)
-> (StartChildWorkflowOptions -> String)
-> ([StartChildWorkflowOptions] -> ShowS)
-> Show StartChildWorkflowOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StartChildWorkflowOptions -> ShowS
showsPrec :: Int -> StartChildWorkflowOptions -> ShowS
$cshow :: StartChildWorkflowOptions -> String
show :: StartChildWorkflowOptions -> String
$cshowList :: [StartChildWorkflowOptions] -> ShowS
showList :: [StartChildWorkflowOptions] -> ShowS
Show, (forall (m :: * -> *).
Quote m =>
StartChildWorkflowOptions -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
StartChildWorkflowOptions -> Code m StartChildWorkflowOptions)
-> Lift StartChildWorkflowOptions
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => StartChildWorkflowOptions -> m Exp
forall (m :: * -> *).
Quote m =>
StartChildWorkflowOptions -> Code m StartChildWorkflowOptions
$clift :: forall (m :: * -> *). Quote m => StartChildWorkflowOptions -> m Exp
lift :: forall (m :: * -> *). Quote m => StartChildWorkflowOptions -> m Exp
$cliftTyped :: forall (m :: * -> *).
Quote m =>
StartChildWorkflowOptions -> Code m StartChildWorkflowOptions
liftTyped :: forall (m :: * -> *).
Quote m =>
StartChildWorkflowOptions -> Code m StartChildWorkflowOptions
Lift)
defaultChildWorkflowOptions :: StartChildWorkflowOptions
defaultChildWorkflowOptions :: StartChildWorkflowOptions
defaultChildWorkflowOptions =
StartChildWorkflowOptions
{ cancellationType :: ChildWorkflowCancellationType
cancellationType = ChildWorkflowCancellationType
ChildWorkflowCancellationAbandon
, parentClosePolicy :: ParentClosePolicy
parentClosePolicy = ParentClosePolicy
ParentClosePolicyUnspecified
, timeoutOptions :: TimeoutOptions
timeoutOptions =
TimeoutOptions
{ executionTimeout :: Maybe Duration
executionTimeout = Maybe Duration
forall a. Maybe a
Nothing
, runTimeout :: Maybe Duration
runTimeout = Maybe Duration
forall a. Maybe a
Nothing
, taskTimeout :: Maybe Duration
taskTimeout = Maybe Duration
forall a. Maybe a
Nothing
}
, retryPolicy :: Maybe RetryPolicy
retryPolicy = Maybe RetryPolicy
forall a. Maybe a
Nothing
, cronSchedule :: Maybe Text
cronSchedule = Maybe Text
forall a. Maybe a
Nothing
, initialMemo :: Map Text Payload
initialMemo = Map Text Payload
forall a. Monoid a => a
mempty
, searchAttributes :: Map SearchAttributeKey SearchAttributeType
searchAttributes = Map SearchAttributeKey SearchAttributeType
forall a. Monoid a => a
mempty
, headers :: Map Text Payload
headers = Map Text Payload
forall a. Monoid a => a
mempty
, workflowIdReusePolicy :: WorkflowIdReusePolicy
workflowIdReusePolicy = WorkflowIdReusePolicy
WorkflowIdReusePolicyUnspecified
, workflowId :: Maybe WorkflowId
workflowId = Maybe WorkflowId
forall a. Maybe a
Nothing
, taskQueue :: Maybe TaskQueue
taskQueue = Maybe TaskQueue
forall a. Maybe a
Nothing
}
data ContinueAsNewOptions = ContinueAsNewOptions
{ ContinueAsNewOptions -> Maybe TaskQueue
taskQueue :: Maybe TaskQueue
, ContinueAsNewOptions -> Maybe Duration
runTimeout :: Maybe Duration
, ContinueAsNewOptions -> Maybe Duration
taskTimeout :: Maybe Duration
, ContinueAsNewOptions -> Maybe RetryPolicy
retryPolicy :: Maybe RetryPolicy
, ContinueAsNewOptions -> Map Text Payload
memo :: Map Text Payload
, ContinueAsNewOptions -> Map SearchAttributeKey SearchAttributeType
searchAttributes :: Map SearchAttributeKey SearchAttributeType
, :: Map Text Payload
}
deriving stock (ContinueAsNewOptions -> ContinueAsNewOptions -> Bool
(ContinueAsNewOptions -> ContinueAsNewOptions -> Bool)
-> (ContinueAsNewOptions -> ContinueAsNewOptions -> Bool)
-> Eq ContinueAsNewOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ContinueAsNewOptions -> ContinueAsNewOptions -> Bool
== :: ContinueAsNewOptions -> ContinueAsNewOptions -> Bool
$c/= :: ContinueAsNewOptions -> ContinueAsNewOptions -> Bool
/= :: ContinueAsNewOptions -> ContinueAsNewOptions -> Bool
Eq, Int -> ContinueAsNewOptions -> ShowS
[ContinueAsNewOptions] -> ShowS
ContinueAsNewOptions -> String
(Int -> ContinueAsNewOptions -> ShowS)
-> (ContinueAsNewOptions -> String)
-> ([ContinueAsNewOptions] -> ShowS)
-> Show ContinueAsNewOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ContinueAsNewOptions -> ShowS
showsPrec :: Int -> ContinueAsNewOptions -> ShowS
$cshow :: ContinueAsNewOptions -> String
show :: ContinueAsNewOptions -> String
$cshowList :: [ContinueAsNewOptions] -> ShowS
showList :: [ContinueAsNewOptions] -> ShowS
Show, (forall (m :: * -> *). Quote m => ContinueAsNewOptions -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
ContinueAsNewOptions -> Code m ContinueAsNewOptions)
-> Lift ContinueAsNewOptions
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => ContinueAsNewOptions -> m Exp
forall (m :: * -> *).
Quote m =>
ContinueAsNewOptions -> Code m ContinueAsNewOptions
$clift :: forall (m :: * -> *). Quote m => ContinueAsNewOptions -> m Exp
lift :: forall (m :: * -> *). Quote m => ContinueAsNewOptions -> m Exp
$cliftTyped :: forall (m :: * -> *).
Quote m =>
ContinueAsNewOptions -> Code m ContinueAsNewOptions
liftTyped :: forall (m :: * -> *).
Quote m =>
ContinueAsNewOptions -> Code m ContinueAsNewOptions
Lift)
defaultContinueAsNewOptions :: ContinueAsNewOptions
defaultContinueAsNewOptions :: ContinueAsNewOptions
defaultContinueAsNewOptions =
ContinueAsNewOptions
{ taskQueue :: Maybe TaskQueue
taskQueue = Maybe TaskQueue
forall a. Maybe a
Nothing
, runTimeout :: Maybe Duration
runTimeout = Maybe Duration
forall a. Maybe a
Nothing
, taskTimeout :: Maybe Duration
taskTimeout = Maybe Duration
forall a. Maybe a
Nothing
, retryPolicy :: Maybe RetryPolicy
retryPolicy = Maybe RetryPolicy
forall a. Maybe a
Nothing
, memo :: Map Text Payload
memo = Map Text Payload
forall a. Monoid a => a
mempty
, searchAttributes :: Map SearchAttributeKey SearchAttributeType
searchAttributes = Map SearchAttributeKey SearchAttributeType
forall a. Monoid a => a
mempty
, headers :: Map Text Payload
headers = Map Text Payload
forall a. Monoid a => a
mempty
}