Safe Haskell | None |
---|---|
Language | Haskell2010 |
Temporal.Client
Description
Workflow Clients are embedded in your application code and connect to a Temporal Server.
They are used to start new workflows and to signal existing workflows.
Synopsis
- data WorkflowClient
- workflowClient :: MonadIO m => Client -> WorkflowClientConfig -> m WorkflowClient
- data WorkflowClientConfig = WorkflowClientConfig {}
- mkWorkflowClientConfig :: Namespace -> WorkflowClientConfig
- class HasWorkflowClient (m :: Type -> Type) where
- data StartWorkflowOptions = StartWorkflowOptions {
- taskQueue :: TaskQueue
- followRuns :: Bool
- workflowIdReusePolicy :: Maybe WorkflowIdReusePolicy
- retryPolicy :: Maybe RetryPolicy
- cronSchedule :: Maybe Text
- memo :: !(Map Text Payload)
- searchAttributes :: !(Map SearchAttributeKey SearchAttributeType)
- headers :: !(Map Text Payload)
- timeouts :: TimeoutOptions
- requestEagerExecution :: Bool
- workflowStartDelay :: Maybe Duration
- data TimeoutOptions = TimeoutOptions {}
- startWorkflowOptions :: TaskQueue -> StartWorkflowOptions
- start :: forall (m :: Type -> Type) wf. (MonadIO m, HasWorkflowClient m, WorkflowRef wf) => wf -> WorkflowId -> StartWorkflowOptions -> WorkflowArgs wf :->: m (WorkflowHandle (WorkflowResult wf))
- startFromPayloads :: forall m (args :: [Type]) result. (MonadIO m, HasWorkflowClient m) => KnownWorkflow args result -> WorkflowId -> StartWorkflowOptions -> Vector UnencodedPayload -> m (WorkflowHandle result)
- data WorkflowHandle a
- execute :: forall (m :: Type -> Type) wf. (HasWorkflowClient m, MonadIO m, WorkflowRef wf) => wf -> WorkflowId -> StartWorkflowOptions -> WorkflowArgs wf :->: m (WorkflowResult wf)
- waitWorkflowResult :: (Typeable a, MonadIO m) => WorkflowHandle a -> m a
- data TerminationOptions = TerminationOptions {}
- terminate :: MonadIO m => WorkflowHandle a -> TerminationOptions -> m ()
- data QueryOptions = QueryOptions {}
- data QueryRejectCondition
- data QueryRejected = QueryRejected {}
- data WorkflowExecutionStatus
- defaultQueryOptions :: QueryOptions
- query :: forall (m :: Type -> Type) query a. (MonadIO m, QueryRef query) => WorkflowHandle a -> query -> QueryOptions -> QueryArgs query :->: m (Either QueryRejected (QueryResult query))
- data SignalOptions = SignalOptions {}
- data KnownSignal (args :: [Type]) = (ApplyPayloads codec args, GatherArgs codec args) => KnownSignal {
- signalName :: Text
- signalCodec :: codec
- signal :: forall (m :: Type -> Type) sig a. (MonadIO m, SignalRef sig) => WorkflowHandle a -> sig -> SignalOptions -> SignalArgs sig :->: m ()
- defaultSignalOptions :: SignalOptions
- signalWithStart :: forall wf sig (m :: Type -> Type). (MonadIO m, HasWorkflowClient m, WorkflowRef wf, SignalRef sig) => wf -> WorkflowId -> StartWorkflowOptions -> sig -> WorkflowArgs wf :->: (SignalArgs sig :->: m (WorkflowHandle (WorkflowResult wf)))
- getHandle :: forall m (args :: [Type]) a. (HasWorkflowClient m, MonadIO m) => KnownWorkflow args a -> WorkflowId -> Maybe RunId -> m (WorkflowHandle a)
- fetchHistory :: MonadIO m => WorkflowHandle a -> m History
- streamEvents :: forall (m :: Type -> Type). (MonadIO m, HasWorkflowClient m) => FollowOption -> GetWorkflowExecutionHistoryRequest -> ConduitT () HistoryEvent m ()
- data FollowOption
Workflow Client
data WorkflowClient Source #
Instances
Monad m => HasWorkflowClient (ReaderT WorkflowClient m) Source # | |
Defined in Temporal.Client Methods askWorkflowClient :: ReaderT WorkflowClient m WorkflowClient Source # | |
HasWorkflowClient ((->) WorkflowClient) Source # | |
Defined in Temporal.Client Methods askWorkflowClient :: WorkflowClient -> WorkflowClient Source # | |
Monad m => HasWorkflowClient (RWST WorkflowClient w s m) Source # | |
Defined in Temporal.Client Methods askWorkflowClient :: RWST WorkflowClient w s m WorkflowClient Source # | |
(Monad m, Monoid w) => HasWorkflowClient (RWST WorkflowClient w s m) Source # | |
Defined in Temporal.Client Methods askWorkflowClient :: RWST WorkflowClient w s m WorkflowClient Source # | |
(Monad m, Monoid w) => HasWorkflowClient (RWST WorkflowClient w s m) Source # | |
Defined in Temporal.Client Methods askWorkflowClient :: RWST WorkflowClient w s m WorkflowClient Source # |
workflowClient :: MonadIO m => Client -> WorkflowClientConfig -> m WorkflowClient Source #
data WorkflowClientConfig Source #
Constructors
WorkflowClientConfig | |
Fields
|
class HasWorkflowClient (m :: Type -> Type) where Source #
Methods
Instances
Running Workflows
data StartWorkflowOptions Source #
Configuration parameters for starting a workflow execution.
Constructors
StartWorkflowOptions | |
Fields
|
Instances
Show StartWorkflowOptions Source # | |
Defined in Temporal.Client.Types Methods showsPrec :: Int -> StartWorkflowOptions -> ShowS # show :: StartWorkflowOptions -> String # showList :: [StartWorkflowOptions] -> ShowS # | |
Eq StartWorkflowOptions Source # | |
Defined in Temporal.Client.Types Methods (==) :: StartWorkflowOptions -> StartWorkflowOptions -> Bool # (/=) :: StartWorkflowOptions -> StartWorkflowOptions -> Bool # | |
Lift StartWorkflowOptions Source # | |
Defined in Temporal.Client.Types Methods lift :: Quote m => StartWorkflowOptions -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => StartWorkflowOptions -> Code m StartWorkflowOptions # |
data TimeoutOptions Source #
Constructors
TimeoutOptions | |
Fields
|
Instances
startWorkflowOptions :: TaskQueue -> StartWorkflowOptions Source #
Smart constructor for StartWorkflowOptions
.
At a minimum, a Workflow
execution requires a WorkflowId
and a TaskQueue
.
It is recommend to specify WorkflowId
in most cases, as it is used to uniquely identify a Workflow
execution,
but if one is not specified then a random UUID will be generated.
start :: forall (m :: Type -> Type) wf. (MonadIO m, HasWorkflowClient m, WorkflowRef wf) => wf -> WorkflowId -> StartWorkflowOptions -> WorkflowArgs wf :->: m (WorkflowHandle (WorkflowResult wf)) Source #
Begin a new Workflow Execution.
This function does not wait for the Workflow to complete. Instead, it returns a WorkflowHandle
that can be used to wait for the Workflow to complete or perform other operations.
This can be used to "fire-and-forget" a Workflow by discarding the handle.
Arguments
:: forall m (args :: [Type]) result. (MonadIO m, HasWorkflowClient m) | |
=> KnownWorkflow args result | |
-> WorkflowId | A Workflow Id is a customizable, application-level identifier for a Workflow Execution that is unique to an Open Workflow Execution within a Namespace. A Workflow Id is meant to be a business-process identifier such as customer identifier or order identifier. A Workflow Id Reuse Policy can be used to manage whether a Workflow Id can be re-used. The Temporal Platform guarantees uniqueness of the Workflow Id within a Namespace based on the Workflow Id Reuse Policy. A Workflow Execution can be uniquely identified across all Namespaces by its Namespace, Workflow Id, and Run Id. |
-> StartWorkflowOptions | |
-> Vector UnencodedPayload | |
-> m (WorkflowHandle result) |
Start a new Workflow Execution from an unchecked list of payloads. This can be useful if you are forwarding execution from another Workflow or from an external source, but no checking to make sure that the input types are correct is performed.
data WorkflowHandle a Source #
Instances
Functor WorkflowHandle Source # | |
Defined in Temporal.Client.Types Methods fmap :: (a -> b) -> WorkflowHandle a -> WorkflowHandle b # (<$) :: a -> WorkflowHandle b -> WorkflowHandle a # |
execute :: forall (m :: Type -> Type) wf. (HasWorkflowClient m, MonadIO m, WorkflowRef wf) => wf -> WorkflowId -> StartWorkflowOptions -> WorkflowArgs wf :->: m (WorkflowResult wf) Source #
Run a workflow, synchronously waiting for it to complete.
This function will block until the workflow completes, and will return the result of the workflow
or throw a WorkflowExecutionClosed
exception if the workflow was closed without returning a result.
waitWorkflowResult :: (Typeable a, MonadIO m) => WorkflowHandle a -> m a Source #
Given a WorkflowHandle
, wait for the workflow to complete and return the result.
This function will block until the workflow completes, and will return the result of the workflow
or throw a WorkflowExecutionClosed
exception if the workflow was closed without returning a result.
Closing Workflows
data TerminationOptions Source #
Constructors
TerminationOptions | |
Fields
|
terminate :: MonadIO m => WorkflowHandle a -> TerminationOptions -> m () Source #
Terminating a workflow immediately signals to the worker that the workflow should cease execution. The workflow will not be given a chance to react to the termination.
Querying Workflows
data QueryOptions Source #
Constructors
QueryOptions | |
Fields |
data QueryRejectCondition Source #
QueryRejectCondition can used to reject the query if workflow state does not satisfy condition.
Constructors
QueryRejectConditionRejectNone | indicates that query should not be rejected |
QueryRejectConditionNotOpen | indicates that query should be rejected if workflow is not open |
QueryRejectConditionNotCompletedCleanly | indicates that query should be rejected if workflow did not complete cleanly |
data QueryRejected Source #
Constructors
QueryRejected | |
Fields |
Instances
Read QueryRejected Source # | |
Defined in Temporal.Client.Types Methods readsPrec :: Int -> ReadS QueryRejected # readList :: ReadS [QueryRejected] # | |
Show QueryRejected Source # | |
Defined in Temporal.Client.Types Methods showsPrec :: Int -> QueryRejected -> ShowS # show :: QueryRejected -> String # showList :: [QueryRejected] -> ShowS # | |
Eq QueryRejected Source # | |
Defined in Temporal.Client.Types Methods (==) :: QueryRejected -> QueryRejected -> Bool # (/=) :: QueryRejected -> QueryRejected -> Bool # | |
Ord QueryRejected Source # | |
Defined in Temporal.Client.Types Methods compare :: QueryRejected -> QueryRejected -> Ordering # (<) :: QueryRejected -> QueryRejected -> Bool # (<=) :: QueryRejected -> QueryRejected -> Bool # (>) :: QueryRejected -> QueryRejected -> Bool # (>=) :: QueryRejected -> QueryRejected -> Bool # max :: QueryRejected -> QueryRejected -> QueryRejected # min :: QueryRejected -> QueryRejected -> QueryRejected # |
data WorkflowExecutionStatus Source #
Constructors
Running | |
Completed | |
Failed | |
Canceled | |
Terminated | |
ContinuedAsNew | |
TimedOut | |
UnknownStatus |
Instances
query :: forall (m :: Type -> Type) query a. (MonadIO m, QueryRef query) => WorkflowHandle a -> query -> QueryOptions -> QueryArgs query :->: m (Either QueryRejected (QueryResult query)) Source #
A Query is a synchronous operation that is used to get the state of a Workflow Execution. The state of a running Workflow Execution is constantly changing. You can use Queries to expose the internal Workflow Execution state to the external world. Queries are available for running or completed Workflows Executions only if the Worker is up and listening on the Task Queue.
Queries are sent from a Temporal Client to a Workflow Execution. The API call is synchronous. The Query is identified at both ends by a Query name. The Workflow must have a Query handler that is developed to handle that Query and provide data that represents the state of the Workflow Execution.
Queries are strongly consistent and are guaranteed to return the most recent state. This means that the data reflects the state of all confirmed Events that came in before the Query was sent. An Event is considered confirmed if the call creating the Event returned success. Events that are created while the Query is outstanding may or may not be reflected in the Workflow state the Query result is based on.
A Query can carry arguments to specify the data it is requesting. And each Workflow can expose data to multiple types of Queries.
A Query must never mutate the state of the Workflow Execution—that is, Queries are read-only and cannot contain any blocking code. This means, for example, that Query handling logic cannot schedule Activity Executions.
For the Haskell library, this means that the only state that is accessible to a Query is Info
and values in StateVar
s.
Sending Queries to completed Workflow Executions is supported, though Query reject conditions can be configured per Query.
Sending Signals to Workflows
data SignalOptions Source #
Constructors
SignalOptions | |
data KnownSignal (args :: [Type]) Source #
Constructors
(ApplyPayloads codec args, GatherArgs codec args) => KnownSignal | |
Fields
|
Instances
SignalRef (KnownSignal args) Source # | |||||
Defined in Temporal.Workflow.Signal Associated Types
Methods signalRef :: KnownSignal args -> KnownSignal (SignalArgs (KnownSignal args)) Source # | |||||
type SignalArgs (KnownSignal args) Source # | |||||
Defined in Temporal.Workflow.Signal |
signal :: forall (m :: Type -> Type) sig a. (MonadIO m, SignalRef sig) => WorkflowHandle a -> sig -> SignalOptions -> SignalArgs sig :->: m () Source #
A Signal is an asynchronous request to a Workflow Execution.
A Signal delivers data to a running Workflow Execution. It cannot return data to the caller; to do so, use a Query instead. The Workflow code that handles a Signal can mutate Workflow state. A Signal can be sent from a Temporal Client or a Workflow. When a Signal is sent, it is received by the Cluster and recorded as an Event to the Workflow Execution Event History. A successful response from the Cluster means that the Signal has been persisted and will be delivered at least once to the Workflow Execution. The next scheduled Workflow Task will contain the Signal Event.
Signal handlers are Workflow functions that listen for Signals by the Signal name. Signals are delivered in the order they are received by the Cluster. If multiple deliveries of a Signal would be a problem for your Workflow, add idempotency logic to your Signal handler that checks for duplicates.
signalWithStart :: forall wf sig (m :: Type -> Type). (MonadIO m, HasWorkflowClient m, WorkflowRef wf, SignalRef sig) => wf -> WorkflowId -> StartWorkflowOptions -> sig -> WorkflowArgs wf :->: (SignalArgs sig :->: m (WorkflowHandle (WorkflowResult wf))) Source #
If there is a running Workflow Execution with the given Workflow Id, it will be Signaled.
Otherwise, a new Workflow Execution is started and immediately send the Signal.
Producing handles for existing workflows
getHandle :: forall m (args :: [Type]) a. (HasWorkflowClient m, MonadIO m) => KnownWorkflow args a -> WorkflowId -> Maybe RunId -> m (WorkflowHandle a) Source #
Sometimes you know that a Workflow exists or existed, but you didn't create the workflow from
the current process or code path. In this case, you can use getHandle
to get a handle to the
workflow so that you can interact with it.
Note that it is possible for a workflow to be closed or archived by the time you get a handle,
so you should be prepared to handle WorkflowExecutionClosed
exceptions.
Workflow history utilities
fetchHistory :: MonadIO m => WorkflowHandle a -> m History Source #
Fetch the history of a Workflow execution as it currently stands.
This is useful for Workflow replay tests.
streamEvents :: forall (m :: Type -> Type). (MonadIO m, HasWorkflowClient m) => FollowOption -> GetWorkflowExecutionHistoryRequest -> ConduitT () HistoryEvent m () Source #
Workflow execution history is represented as a series of events. This function allows you to
subscribe to those events and process them as they are received. As an example, this is used to implement
waitWorkflowResult
.
data FollowOption Source #
Constructors
FollowRuns | |
ThisRunOnly |