temporal-sdk
Safe HaskellNone
LanguageHaskell2010

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

Workflow Client

data WorkflowClientConfig Source #

Constructors

WorkflowClientConfig 

Fields

class HasWorkflowClient (m :: Type -> Type) where Source #

Instances

Instances details
HasWorkflowClient (Activity env) Source # 
Instance details

Defined in Temporal.Activity

(Monad m, HasWorkflowClient m) => HasWorkflowClient (MaybeT m) Source # 
Instance details

Defined in Temporal.Client

(Monad m, HasWorkflowClient m, Monoid w) => HasWorkflowClient (AccumT w m) Source # 
Instance details

Defined in Temporal.Client

(Monad m, HasWorkflowClient m) => HasWorkflowClient (ExceptT e m) Source # 
Instance details

Defined in Temporal.Client

(Monad m, HasWorkflowClient m) => HasWorkflowClient (IdentityT m) Source # 
Instance details

Defined in Temporal.Client

Monad m => HasWorkflowClient (ReaderT WorkflowClient m) Source # 
Instance details

Defined in Temporal.Client

(Monad m, HasWorkflowClient m) => HasWorkflowClient (ReaderT r m) Source # 
Instance details

Defined in Temporal.Client

(Monad m, HasWorkflowClient m) => HasWorkflowClient (SelectT r m) Source # 
Instance details

Defined in Temporal.Client

(Monad m, HasWorkflowClient m) => HasWorkflowClient (StateT s m) Source # 
Instance details

Defined in Temporal.Client

(Monad m, HasWorkflowClient m) => HasWorkflowClient (StateT s m) Source # 
Instance details

Defined in Temporal.Client

(Monad m, HasWorkflowClient m) => HasWorkflowClient (WriterT w m) Source # 
Instance details

Defined in Temporal.Client

(Monad m, HasWorkflowClient m, Monoid w) => HasWorkflowClient (WriterT w m) Source # 
Instance details

Defined in Temporal.Client

(Monad m, HasWorkflowClient m, Monoid w) => HasWorkflowClient (WriterT w m) Source # 
Instance details

Defined in Temporal.Client

(Monad m, HasWorkflowClient m) => HasWorkflowClient (ConduitT i o m) Source # 
Instance details

Defined in Temporal.Client

(Monad m, HasWorkflowClient m) => HasWorkflowClient (ContT r m) Source # 
Instance details

Defined in Temporal.Client

HasWorkflowClient ((->) WorkflowClient) Source # 
Instance details

Defined in Temporal.Client

Monad m => HasWorkflowClient (RWST WorkflowClient w s m) Source # 
Instance details

Defined in Temporal.Client

(Monad m, HasWorkflowClient m) => HasWorkflowClient (RWST r w s m) Source # 
Instance details

Defined in Temporal.Client

(Monad m, Monoid w) => HasWorkflowClient (RWST WorkflowClient w s m) Source # 
Instance details

Defined in Temporal.Client

(Monad m, HasWorkflowClient m, Monoid w) => HasWorkflowClient (RWST r w s m) Source # 
Instance details

Defined in Temporal.Client

(Monad m, Monoid w) => HasWorkflowClient (RWST WorkflowClient w s m) Source # 
Instance details

Defined in Temporal.Client

(Monad m, HasWorkflowClient m, Monoid w) => HasWorkflowClient (RWST r w s m) Source # 
Instance details

Defined in Temporal.Client

Running Workflows

data StartWorkflowOptions Source #

Configuration parameters for starting a workflow execution.

Constructors

StartWorkflowOptions 

Fields

  • taskQueue :: TaskQueue

    A Task Queue is a lightweight, dynamically allocated queue that one or more Worker Entities poll for Tasks.

    Task Queues are very lightweight components. Task Queues do not require explicit registration but instead are created on demand when a Workflow Execution spawns or when a Worker Process subscribes to it. When a Task Queue is created, both a Workflow Task Queue and an Activity Task Queue are created under the same name. There is no limit to the number of Task Queues a Temporal Application can use or a Temporal Cluster can maintain.

  • followRuns :: Bool
     
  • workflowIdReusePolicy :: Maybe WorkflowIdReusePolicy

    A Workflow Id Reuse Policy determines whether a Workflow Execution is allowed to spawn with a particular Workflow Id, if that Workflow Id has been used with a previous, and now Closed, Workflow Execution.

    It is not possible for a new Workflow Execution to spawn with the same Workflow Id as another Open Workflow Execution, regardless of the Workflow Id Reuse Policy. In some cases, an attempt to spawn a Workflow Execution with a Workflow Id that is the same as the Id of a currently Open Workflow Execution results in a Workflow execution already started error.

  • retryPolicy :: Maybe RetryPolicy

    A Retry Policy can work in cooperation with the timeouts to provide fine controls to optimize the execution experience.

    Use a Retry Policy to retry a Workflow Execution in the event of a failure.

    Workflow Executions do not retry by default, and Retry Policies should be used with Workflow Executions only in certain situations.

    This should not be confused with Activity retry policies, which are used to retry Activities and specified at those callsites.

  • cronSchedule :: Maybe Text

    A Temporal Cron Job is the series of Workflow Executions that occur when a Cron Schedule is provided in the call to spawn a Workflow Execution.

    A Cron Schedule is provided as an option when the call to spawn a Workflow Execution is made.

    You can set each Workflow to repeat on a schedule with the cronSchedule option:

    Temporal.Client.start scheduledWorkflow
      (Temporal.Client.startWorkflowOptions "my-workflow" "my-task-queue") { cronSchedule = Just "* * * * *" } -- start every minute
    

    Note that Temporal offers more advanced scheduling support via Schedule, so it is generally recommended to use that instead of Cron Schedules.

  • memo :: !(Map Text Payload)

    A Memo is a non-indexed set of Workflow Execution metadata that developers supply at start time or in Workflow code and that is returned when you describe or list Workflow Executions.

    The primary purpose of using a Memo is to enhance the organization and management of Workflow Executions. Add your own metadata, such as notes or descriptions, to a Workflow Execution, which lets you annotate and categorize Workflow Executions based on developer-defined criteria. This feature is particularly useful when dealing with numerous Workflow Executions because it facilitates the addition of context, reminders, or any other relevant information that aids in understanding or tracking the Workflow Execution.

  • searchAttributes :: !(Map SearchAttributeKey SearchAttributeType)

    Search attributes are indexed by the Temporal server and can be used in queries on the dashboard or by the Temporal CLI to find Workflows. These values are not encrypted and can be seen by anyone with access to the Temporal namespace.

  • headers :: !(Map Text Payload)

    Custom headers to be added to the Workflow Execution. These are generally more useful for interceptors to add metadata to the Workflow rather than for application code.

  • timeouts :: TimeoutOptions

    Each Workflow timeout controls the maximum duration of a different aspect of a Workflow Execution.

  • requestEagerExecution :: Bool

    Eager activity execution is an optimization on some servers that sends activities back to the same worker as the calling workflow if they can run there.

  • workflowStartDelay :: Maybe Duration
     

data TimeoutOptions Source #

Constructors

TimeoutOptions 

Fields

  • executionTimeout :: Maybe Duration

    A Workflow Execution Timeout is the maximum time that a Workflow Execution can be executing (have an Open status) including retries and any usage of Continue As New.

    The default value is ∞ (infinite). If this timeout is reached, the Workflow Execution changes to a Timed Out status. This timeout is different from the Workflow Run Timeout. This timeout is most commonly used for stopping the execution of a Temporal Cron Job after a certain amount of time has passed.

  • runTimeout :: Maybe Duration

    A Workflow Run Timeout is the maximum amount of time that a single Workflow Run is restricted to.

    The default is set to the same value as the Workflow Execution Timeout. This timeout is most commonly used to limit the execution time of a single Temporal Cron Job Execution.

    If the Workflow Run Timeout is reached, the Workflow Execution is Terminated.

  • taskTimeout :: Maybe Duration

    A Workflow Task Timeout is the maximum amount of time allowed for a Worker to execute a Workflow Task after the Worker has pulled that Workflow Task from the Task Queue.

    The default value is 10 seconds. This timeout is primarily available to recognize whether a Worker has gone down so that the Workflow Execution can be recovered on a different Worker. The main reason for increasing the default value would be to accommodate a Workflow Execution that has a very long Workflow Execution History that could take longer than 10 seconds for the Worker to load.

Instances

Instances details
Data TimeoutOptions Source # 
Instance details

Defined in Temporal.Common

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeoutOptions -> c TimeoutOptions #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeoutOptions #

toConstr :: TimeoutOptions -> Constr #

dataTypeOf :: TimeoutOptions -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TimeoutOptions) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeoutOptions) #

gmapT :: (forall b. Data b => b -> b) -> TimeoutOptions -> TimeoutOptions #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeoutOptions -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeoutOptions -> r #

gmapQ :: (forall d. Data d => d -> u) -> TimeoutOptions -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TimeoutOptions -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TimeoutOptions -> m TimeoutOptions #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeoutOptions -> m TimeoutOptions #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeoutOptions -> m TimeoutOptions #

Show TimeoutOptions Source # 
Instance details

Defined in Temporal.Common

Eq TimeoutOptions Source # 
Instance details

Defined in Temporal.Common

Lift TimeoutOptions Source # 
Instance details

Defined in Temporal.Common

Methods

lift :: Quote m => TimeoutOptions -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => TimeoutOptions -> Code m TimeoutOptions #

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.

startFromPayloads Source #

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

Instances details
Functor WorkflowHandle Source # 
Instance details

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 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 WorkflowExecutionStatus Source #

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 StateVars.

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 

Fields

data KnownSignal (args :: [Type]) Source #

Constructors

(ApplyPayloads codec args, GatherArgs codec args) => KnownSignal 

Fields

Instances

Instances details
SignalRef (KnownSignal args) Source # 
Instance details

Defined in Temporal.Workflow.Signal

Associated Types

type SignalArgs (KnownSignal args) 
Instance details

Defined in Temporal.Workflow.Signal

type SignalArgs (KnownSignal args) = args
type SignalArgs (KnownSignal args) Source # 
Instance details

Defined in Temporal.Workflow.Signal

type SignalArgs (KnownSignal args) = args

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.