temporal-sdk
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Temporal.TH

Description

The TH module provides Template Haskell-based utilities for defining, configuring, and registering Temporal Workflows and Activities in a type-safe and declarative manner. This module simplifies the process of integrating Temporal with Haskell applications by automating much of the boilerplate code typically required for setting up Workflows and Activities.

Key features of this module include:

  1. Automatic registration of Workflows and Activities.
  2. Type-safe configuration options for both Workflows and Activities.
  3. Generation of necessary typeclass instances for Workflow and Activity functions.
  4. Support for custom naming and aliasing of Activities.
  5. Integration with Haskell's strong type system to ensure correctness at compile-time.

The main functions provided by this module are:

When you apply the registration functions to your Workflow and Activity functions, a number of things happen automatically:

  1. The registration functions generate a new data type with the same name as your Workflow or Activity function (capitalized). Example: If you define a Workflow function named myWorkflow, the generated data type will be named MyWorkflow.
  2. A number of type classes are generated or derived for your Workflow or Activity function to support invoking them.

Example usage:

{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ImportQualifiedPost #-}

module MyWorkflows where

import Language.Haskell.TH (newDeclarationGroup)
import RequireCallStack (provideCallStack)
import Temporal.Activity
import Temporal.TH
import Temporal.TH.Options
import Temporal.Workflow
import Temporal.Client qualified as Client

-- Simple activity registration
actWithoutTimeoutDefault :: Activity () ()
actWithoutTimeoutDefault = pure ()
$(registerActivity 'actWithoutTimeoutDefault)

-- Activity registration with name override
actWithNameOverride :: Activity () ()
actWithNameOverride = pure ()
$(registerActivityWithOptions 'actWithNameOverride defaultActivityConfiguration
  { actNameOverride = Just "my-name"
  })

-- Activity registration with aliases
actWithAliases :: Activity () ()
actWithAliases = pure ()
$(registerActivityWithOptions 'actWithAliases defaultActivityConfiguration
  { actAliases = ["alias1", "alias2"]
  })

-- Workflow registration
myWorkflow :: Int -> Workflow ()
myWorkflow _ = pure ()
$(registerWorkflow 'myWorkflow)

-- Use newDeclarationGroup to separate Template Haskell splices
$(newDeclarationGroup)

-- Workflow referencing a child workflow
workflowReferencingChild :: Workflow ()
workflowReferencingChild = provideCallStack do
  _ <- startChildWorkflow MyWorkflow defaultChildWorkflowOptions 0
  executeChildWorkflow MyWorkflow defaultChildWorkflowOptions 1

-- Activity referencing a workflow
actionReferencingWorkflow :: Activity () ()
actionReferencingWorkflow = provideCallStack do
  _ <- Client.start MyWorkflow "1" (Client.startWorkflowOptions (TaskQueue "foo")) 1
  Client.execute MyWorkflow "2" (Client.startWorkflowOptions (TaskQueue "foo")) 1

Note the use of newDeclarationGroup from Language.Haskell.TH to separate Template Haskell splices, which can be necessary in some cases to avoid compilation errors– namely, when you want to invoke a Workflow or Activity later in the same module.

The one use case where the TH mechanism struggles is when you want to use the continueAsNew function from Temporal.Workflow in a Workflow to start a new instance of the same Workflow. In this case, you can define the machinery manually:

workflowThatContinuesAsNew :: Int -> Workflow ()
workflowThatContinuesAsNew x = do
  if x < 1000
  then continueAsNew WorkflowThatContinuesAsNew defaultContinueAsNewOptions (x + 1)
  else return ()

data WorkflowThatContinuesAsNew = WorkflowThatContinuesAsNew
  deriving anyclass (WorkflowFn)
  deriving (WorkflowDef, WorkflowRef) via WorkflowImpl WorkflowThatContinuesAsNew

instance Fn WorkflowThatContinuesAsNew where
  fnName = Text.pack $ show 'workflowThatContinuesAsNew
  fnDefinition _ = provideCallStack workflowThatContinuesAsNew
  fnSing = WorkflowThatContinuesAsNew
Synopsis

Documentation

type SomeDict = SomeDictOf (Proxy :: k -> Type) #

In the case where you only need evidence that the dictionary exists, then you can use this type. By carrying a Proxy instead of a real value, we can summon these up whenever we have an instance of the type in question.

This is useful when you have a type class that specifies some *static* behavior that is useful, or a type class that can provide means of creatingretrievingworking with data. Consider the PersistEntity class from the persistent database library. An instance of that class can be used to get the EntityDef that describes how the type interacts with the database, or you can even selectList and grab all entities out of the database.

someEntity :: SomeDict PersistEntity
someEntity = someDict @User

With this value, we can now extract the EntityDef:

someEntityDef :: EntityDef
someEntityDef =
    case someEntity of
        SomeDictOf (Proxy :: Proxy a) ->
            entityDef (Proxy :: Proxy a)

We can also load all the rows out of the database.

verifyRowsCanLoad :: SqlPersistT IO ()
verifyRowsCanLoad =
    case someEntity of
        SomeDictOf (Proxy :: Proxy a) -> do
            rows <- selectList [] [] :: SqlPersistT IO [Entity a]
            mapM_ (print . entityKey) rows

Since: some-dict-of-0.1.0.0

data SomeDictOf (f :: k -> Type) (c :: k -> Constraint) where #

A datatype that carries evidence of type class membership for some type, along with a datatype indexed by that type. This is confusing, so let's look at some examples.

The alias SomeDict clazz uses Proxy for the datatype index. This means that the wrapper is a Proxy :: Proxy a, and you know that the type a has an instance of clazz a. The SomeDictOf type does not actually *carry* any values of this type.

That is not to say that we *necessarily* won't have a value - consider SomeDictOf Identity, which actually does hold a value. We can use this to make an existential Show wrapper.

showSomeDict :: SomeDictOf Identity Show
showSomeDict =
    SomeDictOf (Identity 3 :: Identity Int)

We can happily have a [SomeDictOf Identity Show], or a Map String (SomeDictOf Identity 'Show), or similar.

Constructing them is easy enough. Consuming them can be a bit trickier. Let's look at a SomeDict Monoid.

monoid :: SomeDictOf Proxy Monoid
monoid =
    SomeDictOf (Proxy :: Proxy Text)

All we know about this is that it's carrying a datatype with a Monoid instance. We'll case-match on the value, and then in the case branch, we'll have evidence that (whatever the underlying type is) that it has a Monoid instance.

We'll repackage the value, but instead of using Proxy, we'll stuff mempty into Identity.

useMonoid :: SomeDictOf Proxy Monoid -> SomeDictOf Identity Monoid
useMonoid someDictOfProxy =
    case someDictOfProxy of
        SomeDictOf (Proxy :: Proxy a) ->
            SomeDictOf (Identity (mempty :: a))

Since: some-dict-of-0.1.0.0

Constructors

SomeDictOf :: forall {k} (c :: k -> Constraint) (a :: k) (f :: k -> Type). c a => f a -> SomeDictOf f c 

registerActivityWithOptions :: forall codec m. (Quote m, Quasi m, Lift codec) => Name -> ActivityConfig codec -> m [Dec] Source #

data ActivityConfig c Source #

Instances

Instances details
Lift c => Lift (ActivityConfig c :: Type) Source # 
Instance details

Defined in Temporal.TH.Classes

Methods

lift :: Quote m => ActivityConfig c -> m Exp #

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

registerWorkflowWithOptions :: forall codec m. (Quote m, Quasi m, Lift codec) => Name -> WorkflowConfig codec -> m [Dec] Source #

data WorkflowConfig codec Source #

Instances

Instances details
Lift codec => Lift (WorkflowConfig codec :: Type) Source # 
Instance details

Defined in Temporal.TH.Classes

Methods

lift :: Quote m => WorkflowConfig codec -> m Exp #

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

Show codec => Show (WorkflowConfig codec) Source # 
Instance details

Defined in Temporal.TH.Classes

Methods

showsPrec :: Int -> WorkflowConfig codec -> ShowS #

show :: WorkflowConfig codec -> String #

showList :: [WorkflowConfig codec] -> ShowS #

class Fn t where Source #

Associated Types

type FnType t Source #

class WorkflowRef f where Source #

Associated Types

type WorkflowArgs f :: [Type] Source #

type WorkflowResult f Source #

Instances

Instances details
(Fn f, WorkflowFn f) => WorkflowRef (WorkflowImpl f) Source # 
Instance details

Defined in Temporal.TH.Classes

Associated Types

type WorkflowArgs (WorkflowImpl f) 
Instance details

Defined in Temporal.TH.Classes

type WorkflowResult (WorkflowImpl f) 
Instance details

Defined in Temporal.TH.Classes

VarArgs (ArgsOf f) => WorkflowRef (ProvidedWorkflow f) Source # 
Instance details

Defined in Temporal.Workflow.Definition

WorkflowRef (KnownWorkflow args result) Source # 
Instance details

Defined in Temporal.Workflow.Definition

Associated Types

type WorkflowArgs (KnownWorkflow args result) 
Instance details

Defined in Temporal.Workflow.Definition

type WorkflowArgs (KnownWorkflow args result) = args
type WorkflowResult (KnownWorkflow args result) 
Instance details

Defined in Temporal.Workflow.Definition

type WorkflowResult (KnownWorkflow args result) = result

Methods

workflowRef :: KnownWorkflow args result -> KnownWorkflow (WorkflowArgs (KnownWorkflow args result)) (WorkflowResult (KnownWorkflow args result)) Source #

class (Fn f, Typeable (FnActivityEnv (FnType f))) => ActivityFn f where Source #

Minimal complete definition

Nothing

Associated Types

type ActivityCodec f Source #

class ActivityRef f where Source #

Associated Types

type ActivityArgs f :: [Type] Source #

type ActivityResult f Source #

Instances

Instances details
(Fn f, ActivityFn f) => ActivityRef (ActivityImpl f) Source # 
Instance details

Defined in Temporal.TH.Classes

Associated Types

type ActivityArgs (ActivityImpl f) 
Instance details

Defined in Temporal.TH.Classes

type ActivityResult (ActivityImpl f) 
Instance details

Defined in Temporal.TH.Classes

(TypeError DirectActivityReferenceMsg :: Constraint) => ActivityRef (Activity env a) Source # 
Instance details

Defined in Temporal.Activity.Definition

Associated Types

type ActivityArgs (Activity env a) 
Instance details

Defined in Temporal.Activity.Definition

type ActivityArgs (Activity env a) = '[] :: [Type]
type ActivityResult (Activity env a) 
Instance details

Defined in Temporal.Activity.Definition

type ActivityResult (Activity env a) = a
VarArgs args => ActivityRef (KnownActivity args result) Source # 
Instance details

Defined in Temporal.Activity.Definition

Associated Types

type ActivityArgs (KnownActivity args result) 
Instance details

Defined in Temporal.Activity.Definition

type ActivityArgs (KnownActivity args result) = args
type ActivityResult (KnownActivity args result) 
Instance details

Defined in Temporal.Activity.Definition

type ActivityResult (KnownActivity args result) = result

Methods

activityRef :: KnownActivity args result -> KnownActivity (ActivityArgs (KnownActivity args result)) (ActivityResult (KnownActivity args result)) Source #

ActivityRef (ProvidedActivity env f) Source # 
Instance details

Defined in Temporal.Activity.Definition

Associated Types

type ActivityArgs (ProvidedActivity env f) 
Instance details

Defined in Temporal.Activity.Definition

type ActivityResult (ProvidedActivity env f) 
Instance details

Defined in Temporal.Activity.Definition

(f ~ (ArgsOf f :->: Activity env (ResultOf (Activity env) f)), TypeError DirectActivityReferenceMsg :: Constraint) => ActivityRef (a -> f) Source # 
Instance details

Defined in Temporal.Activity.Definition

Associated Types

type ActivityArgs (a -> f) 
Instance details

Defined in Temporal.Activity.Definition

type ActivityArgs (a -> f) = '[] :: [Type]
type ActivityResult (a -> f) 
Instance details

Defined in Temporal.Activity.Definition

type ActivityResult (a -> f) = ()

Methods

activityRef :: (a -> f) -> KnownActivity (ActivityArgs (a -> f)) (ActivityResult (a -> f)) Source #

fnSingE :: (Quote m, Quasi m) => Name -> m Exp Source #

newtype ActivityImpl f Source #

Constructors

ActivityImpl f 

Instances

Instances details
(Fn f, ActivityFn f) => ActivityDef (ActivityImpl f) Source # 
Instance details

Defined in Temporal.TH.Classes

Associated Types

type ActivityDefinitionEnv (ActivityImpl f) 
Instance details

Defined in Temporal.TH.Classes

(Fn f, ActivityFn f) => ActivityRef (ActivityImpl f) Source # 
Instance details

Defined in Temporal.TH.Classes

Associated Types

type ActivityArgs (ActivityImpl f) 
Instance details

Defined in Temporal.TH.Classes

type ActivityResult (ActivityImpl f) 
Instance details

Defined in Temporal.TH.Classes

type ActivityArgs (ActivityImpl f) Source # 
Instance details

Defined in Temporal.TH.Classes

type ActivityDefinitionEnv (ActivityImpl f) Source # 
Instance details

Defined in Temporal.TH.Classes

type ActivityResult (ActivityImpl f) Source # 
Instance details

Defined in Temporal.TH.Classes

newtype WorkflowImpl f Source #

Constructors

WorkflowImpl f 

Instances

Instances details
(Fn f, WorkflowFn f) => WorkflowDef (WorkflowImpl f) Source # 
Instance details

Defined in Temporal.TH.Classes

(Fn f, WorkflowFn f) => WorkflowRef (WorkflowImpl f) Source # 
Instance details

Defined in Temporal.TH.Classes

Associated Types

type WorkflowArgs (WorkflowImpl f) 
Instance details

Defined in Temporal.TH.Classes

type WorkflowResult (WorkflowImpl f) 
Instance details

Defined in Temporal.TH.Classes

type WorkflowArgs (WorkflowImpl f) Source # 
Instance details

Defined in Temporal.TH.Classes

type WorkflowResult (WorkflowImpl f) Source # 
Instance details

Defined in Temporal.TH.Classes

bringRegisteredTemporalFunctionsIntoScope :: Q [Dec] Source #

Alias for newDeclarationGroup that makes the intent a bit more clear.