Stability | experimental |
---|---|
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
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:
- Automatic registration of Workflows and Activities.
- Type-safe configuration options for both Workflows and Activities.
- Generation of necessary typeclass instances for Workflow and Activity functions.
- Support for custom naming and aliasing of Activities.
- Integration with Haskell's strong type system to ensure correctness at compile-time.
The main functions provided by this module are:
registerWorkflow
andregisterWorkflowWithOptions
: For registering Workflow functions.registerActivity
andregisterActivityWithOptions
: For registering Activity functions.discoverDefinitions
: For automatically discovering and collecting all defined Workflows and Activities.
When you apply the registration functions to your Workflow and Activity functions, a number of things happen automatically:
- 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 namedMyWorkflow
. - 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
- discoverDefinitions :: (RequireCallStack, Typeable env) => [SomeDict WorkflowFn] -> [SomeDict ActivityFn] -> Definitions env
- type SomeDict = SomeDictOf (Proxy :: k -> Type)
- data SomeDictOf (f :: k -> Type) (c :: k -> Constraint) where
- SomeDictOf :: forall {k} (c :: k -> Constraint) (a :: k) (f :: k -> Type). c a => f a -> SomeDictOf f c
- registerActivity :: (Quote m, Quasi m) => Name -> m [Dec]
- registerActivityWithOptions :: forall codec m. (Quote m, Quasi m, Lift codec) => Name -> ActivityConfig codec -> m [Dec]
- data ActivityConfig c = ActivityConfig {}
- defaultActivityConfig :: ActivityConfig JSON
- registerWorkflow :: (Quote m, Quasi m) => Name -> m [Dec]
- registerWorkflowWithOptions :: forall codec m. (Quote m, Quasi m, Lift codec) => Name -> WorkflowConfig codec -> m [Dec]
- data WorkflowConfig codec = WorkflowConfig {
- workflowConfigNameOverride :: Maybe Text
- workflowConfigAliases :: [Text]
- workflowConfigCodec :: codec
- defaultWorkflowConfig :: WorkflowConfig JSON
- class Fn t where
- type FnType t
- fnName :: t -> Text
- fnDefinition :: t -> RequireCallStack => FnType t
- fnSing :: t
- class Fn f => WorkflowFn f where
- type WorkflowCodec f
- workflowImpl :: f -> ProvidedWorkflow (FnType f)
- workflowConfig :: f -> WorkflowConfig (WorkflowCodec f)
- class WorkflowRef f where
- type WorkflowArgs f :: [Type]
- type WorkflowResult f
- workflowRef :: f -> KnownWorkflow (WorkflowArgs f) (WorkflowResult f)
- class WorkflowDef a where
- workflowDefinition :: a -> WorkflowDefinition
- class (Fn f, Typeable (FnActivityEnv (FnType f))) => ActivityFn f where
- type ActivityCodec f
- activityEnvType :: f -> TypeRep
- activityImpl :: f -> ProvidedActivity (FnActivityEnv (FnType f)) (FnType f)
- activityConfig :: f -> ActivityConfig (ActivityCodec f)
- class ActivityRef f where
- type ActivityArgs f :: [Type]
- type ActivityResult f
- activityRef :: f -> KnownActivity (ActivityArgs f) (ActivityResult f)
- class ActivityDef a where
- type ActivityDefinitionEnv a
- activityDefinition :: a -> ActivityDefinition (ActivityDefinitionEnv a)
- fnSingE :: (Quote m, Quasi m) => Name -> m Exp
- fnSingDataAndConName :: Name -> Name
- newtype ActivityImpl f = ActivityImpl f
- newtype WorkflowImpl f = WorkflowImpl f
- bringRegisteredTemporalFunctionsIntoScope :: Q [Dec]
Documentation
discoverDefinitions :: (RequireCallStack, Typeable env) => [SomeDict WorkflowFn] -> [SomeDict ActivityFn] -> Definitions env Source #
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
uses SomeDict
clazzProxy
for the datatype index. This means
that the wrapper is a
, and you know that the type
Proxy
:: Proxy
aa
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
, which actually does hold a value. We can use this
to make an existential SomeDictOf
Identity
Show
wrapper.
showSomeDict ::SomeDictOf
Identity
Show
showSomeDict =SomeDictOf
(Identity
3 ::Identity
Int
)
We can happily have a [
, or a SomeDictOf
Identity
Show
]Map String
(
, or similar.SomeDictOf
Identity
'Show)
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 #
Constructors
ActivityConfig | |
Fields |
Instances
Lift c => Lift (ActivityConfig c :: Type) Source # | |
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 #
Constructors
WorkflowConfig | |
Fields
|
Instances
Lift codec => Lift (WorkflowConfig codec :: Type) Source # | |
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 # | |
Defined in Temporal.TH.Classes Methods showsPrec :: Int -> WorkflowConfig codec -> ShowS # show :: WorkflowConfig codec -> String # showList :: [WorkflowConfig codec] -> ShowS # |
class Fn f => WorkflowFn f where Source #
Minimal complete definition
Nothing
Methods
workflowImpl :: f -> ProvidedWorkflow (FnType f) Source #
default workflowImpl :: (RequireCallStack, FnType f ~ (ArgsOf (FnType f) :->: Workflow (ResultOf Workflow (FnType f))), FunctionSupportsCodec (WorkflowCodec f) (ArgsOf (FnType f)) (ResultOf Workflow (FnType f))) => f -> ProvidedWorkflow (FnType f) Source #
workflowConfig :: f -> WorkflowConfig (WorkflowCodec f) Source #
default workflowConfig :: WorkflowCodec f ~ JSON => f -> WorkflowConfig (WorkflowCodec f) Source #
class WorkflowRef f where Source #
Methods
workflowRef :: f -> KnownWorkflow (WorkflowArgs f) (WorkflowResult f) Source #
Instances
class WorkflowDef a where Source #
Methods
workflowDefinition :: a -> WorkflowDefinition Source #
Instances
WorkflowDef WorkflowDefinition Source # | |
Defined in Temporal.Workflow.Definition Methods workflowDefinition :: WorkflowDefinition -> WorkflowDefinition Source # | |
(Fn f, WorkflowFn f) => WorkflowDef (WorkflowImpl f) Source # | |
Defined in Temporal.TH.Classes Methods workflowDefinition :: WorkflowImpl f -> WorkflowDefinition Source # | |
WorkflowDef (ProvidedWorkflow f) Source # | |
Defined in Temporal.Workflow.Definition Methods workflowDefinition :: ProvidedWorkflow f -> WorkflowDefinition Source # |
class (Fn f, Typeable (FnActivityEnv (FnType f))) => ActivityFn f where Source #
Minimal complete definition
Nothing
Methods
activityEnvType :: f -> TypeRep Source #
activityImpl :: f -> ProvidedActivity (FnActivityEnv (FnType f)) (FnType f) Source #
default activityImpl :: (RequireCallStack, env ~ FnActivityEnv (FnType f), FnType f ~ (ArgsOf (FnType f) :->: Activity env (ResultOf (Activity env) (FnType f))), FunctionSupportsCodec (ActivityCodec f) (ArgsOf (FnType f)) (ResultOf (Activity env) (FnType f))) => f -> ProvidedActivity (FnActivityEnv (FnType f)) (FnType f) Source #
activityConfig :: f -> ActivityConfig (ActivityCodec f) Source #
default activityConfig :: ActivityCodec f ~ JSON => f -> ActivityConfig (ActivityCodec f) Source #
class ActivityRef f where Source #
Methods
activityRef :: f -> KnownActivity (ActivityArgs f) (ActivityResult f) Source #
Instances
(Fn f, ActivityFn f) => ActivityRef (ActivityImpl f) Source # | |||||||||
Defined in Temporal.TH.Classes Associated Types
Methods activityRef :: ActivityImpl f -> KnownActivity (ActivityArgs (ActivityImpl f)) (ActivityResult (ActivityImpl f)) Source # | |||||||||
(TypeError DirectActivityReferenceMsg :: Constraint) => ActivityRef (Activity env a) Source # | |||||||||
Defined in Temporal.Activity.Definition Associated Types
Methods activityRef :: Activity env a -> KnownActivity (ActivityArgs (Activity env a)) (ActivityResult (Activity env a)) Source # | |||||||||
VarArgs args => ActivityRef (KnownActivity args result) Source # | |||||||||
Defined in Temporal.Activity.Definition Associated Types
Methods activityRef :: KnownActivity args result -> KnownActivity (ActivityArgs (KnownActivity args result)) (ActivityResult (KnownActivity args result)) Source # | |||||||||
ActivityRef (ProvidedActivity env f) Source # | |||||||||
Defined in Temporal.Activity.Definition Associated Types
Methods activityRef :: ProvidedActivity env f -> KnownActivity (ActivityArgs (ProvidedActivity env f)) (ActivityResult (ProvidedActivity env f)) Source # | |||||||||
(f ~ (ArgsOf f :->: Activity env (ResultOf (Activity env) f)), TypeError DirectActivityReferenceMsg :: Constraint) => ActivityRef (a -> f) Source # | |||||||||
Defined in Temporal.Activity.Definition Associated Types
Methods activityRef :: (a -> f) -> KnownActivity (ActivityArgs (a -> f)) (ActivityResult (a -> f)) Source # |
class ActivityDef a where Source #
Associated Types
type ActivityDefinitionEnv a Source #
Methods
activityDefinition :: a -> ActivityDefinition (ActivityDefinitionEnv a) Source #
Instances
ActivityDef (ActivityDefinition env) Source # | |||||
Defined in Temporal.Activity.Definition Associated Types
Methods activityDefinition :: ActivityDefinition env -> ActivityDefinition (ActivityDefinitionEnv (ActivityDefinition env)) Source # | |||||
(Fn f, ActivityFn f) => ActivityDef (ActivityImpl f) Source # | |||||
Defined in Temporal.TH.Classes Associated Types
Methods activityDefinition :: ActivityImpl f -> ActivityDefinition (ActivityDefinitionEnv (ActivityImpl f)) Source # | |||||
ActivityDef (ProvidedActivity env f) Source # | |||||
Defined in Temporal.Activity.Definition Associated Types
Methods activityDefinition :: ProvidedActivity env f -> ActivityDefinition (ActivityDefinitionEnv (ProvidedActivity env f)) Source # |
fnSingDataAndConName :: Name -> Name Source #
newtype ActivityImpl f Source #
Constructors
ActivityImpl f |
Instances
(Fn f, ActivityFn f) => ActivityDef (ActivityImpl f) Source # | |||||||||
Defined in Temporal.TH.Classes Associated Types
Methods activityDefinition :: ActivityImpl f -> ActivityDefinition (ActivityDefinitionEnv (ActivityImpl f)) Source # | |||||||||
(Fn f, ActivityFn f) => ActivityRef (ActivityImpl f) Source # | |||||||||
Defined in Temporal.TH.Classes Associated Types
Methods activityRef :: ActivityImpl f -> KnownActivity (ActivityArgs (ActivityImpl f)) (ActivityResult (ActivityImpl f)) Source # | |||||||||
type ActivityArgs (ActivityImpl f) Source # | |||||||||
Defined in Temporal.TH.Classes | |||||||||
type ActivityDefinitionEnv (ActivityImpl f) Source # | |||||||||
Defined in Temporal.TH.Classes | |||||||||
type ActivityResult (ActivityImpl f) Source # | |||||||||
Defined in Temporal.TH.Classes |
newtype WorkflowImpl f Source #
Constructors
WorkflowImpl f |
Instances
(Fn f, WorkflowFn f) => WorkflowDef (WorkflowImpl f) Source # | |||||||||
Defined in Temporal.TH.Classes Methods workflowDefinition :: WorkflowImpl f -> WorkflowDefinition Source # | |||||||||
(Fn f, WorkflowFn f) => WorkflowRef (WorkflowImpl f) Source # | |||||||||
Defined in Temporal.TH.Classes Associated Types
Methods workflowRef :: WorkflowImpl f -> KnownWorkflow (WorkflowArgs (WorkflowImpl f)) (WorkflowResult (WorkflowImpl f)) Source # | |||||||||
type WorkflowArgs (WorkflowImpl f) Source # | |||||||||
Defined in Temporal.TH.Classes | |||||||||
type WorkflowResult (WorkflowImpl f) Source # | |||||||||
Defined in Temporal.TH.Classes |
bringRegisteredTemporalFunctionsIntoScope :: Q [Dec] Source #
Alias for newDeclarationGroup
that makes the intent a bit more clear.