temporal-sdk
Safe HaskellNone
LanguageHaskell2010

Temporal.Payload

Description

A Payload represents binary data such as input and output from Activities and Workflows. Payloads contain metadata that describe the binary data, such as its data type or other arbitrary values for use by custom encoders/converters.

When processed through the SDK, the default Data Converter serializes your data/value to a Payload before sending it to the Temporal Server. The default Data Converter processes supported type values to Payloads, and you can create a custom Payload Converter to convert your custom object types.

You can additionally apply custom codecs (such as for encryption or compression) on your Payloads to wrap them into new encoded Payloads.

Synopsis

Documentation

data Payload Source #

Instances

Instances details
FromJSON Payload Source # 
Instance details

Defined in Temporal.Payload

ToJSON Payload Source # 
Instance details

Defined in Temporal.Payload

Show Payload Source # 
Instance details

Defined in Temporal.Payload

Eq Payload Source # 
Instance details

Defined in Temporal.Payload

Methods

(==) :: Payload -> Payload -> Bool #

(/=) :: Payload -> Payload -> Bool #

Ord Payload Source # 
Instance details

Defined in Temporal.Payload

Lift Payload Source # 
Instance details

Defined in Temporal.Payload

Methods

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

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

Codec Zlib Payload Source # 
Instance details

Defined in Temporal.Payload

class Codec fmt a where Source #

We want to be able to serialize & deserialize the parameters of a function using an arbitrary serialization format.

Minimal complete definition

encoding, encode, decode

Methods

encoding :: fmt -> Proxy a -> ByteString Source #

Similar to a content-type header, this is a string that identifies the format of the payload. it will be set on the encoding metadata field of the payload.

messageType :: fmt -> a -> ByteString Source #

default messageType :: Typeable a => fmt -> a -> ByteString Source #

encode :: fmt -> a -> IO Payload Source #

decode :: fmt -> Payload -> IO (Either String a) Source #

Instances

Instances details
Codec Binary ByteString Source # 
Instance details

Defined in Temporal.Payload

(Typeable a, ToJSON a, FromJSON a) => Codec JSON a Source # 
Instance details

Defined in Temporal.Payload

Codec Null () Source # 
Instance details

Defined in Temporal.Payload

Message a => Codec Protobuf a Source # 
Instance details

Defined in Temporal.Payload

Codec Zlib Payload Source # 
Instance details

Defined in Temporal.Payload

(Typeable a, Codec base a) => Codec (Around base) a Source # 
Instance details

Defined in Temporal.Payload

Methods

encoding :: Around base -> Proxy a -> ByteString Source #

messageType :: Around base -> a -> ByteString Source #

encode :: Around base -> a -> IO Payload Source #

decode :: Around base -> Payload -> IO (Either String a) Source #

data JSON Source #

Constructors

JSON 

Instances

Instances details
Show JSON Source # 
Instance details

Defined in Temporal.Payload

Methods

showsPrec :: Int -> JSON -> ShowS #

show :: JSON -> String #

showList :: [JSON] -> ShowS #

Eq JSON Source # 
Instance details

Defined in Temporal.Payload

Methods

(==) :: JSON -> JSON -> Bool #

(/=) :: JSON -> JSON -> Bool #

Lift JSON Source # 
Instance details

Defined in Temporal.Payload

Methods

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

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

(Typeable a, ToJSON a, FromJSON a) => Codec JSON a Source # 
Instance details

Defined in Temporal.Payload

data Null Source #

Constructors

Null 

Instances

Instances details
Show Null Source # 
Instance details

Defined in Temporal.Payload

Methods

showsPrec :: Int -> Null -> ShowS #

show :: Null -> String #

showList :: [Null] -> ShowS #

Eq Null Source # 
Instance details

Defined in Temporal.Payload

Methods

(==) :: Null -> Null -> Bool #

(/=) :: Null -> Null -> Bool #

Lift Null Source # 
Instance details

Defined in Temporal.Payload

Methods

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

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

Codec Null () Source # 
Instance details

Defined in Temporal.Payload

data Binary Source #

Direct binary serialization.

A generalized instance like the one for JSON is not provided because there are many possible binary serialization formats and libraries.

You can provide a simple version of this instance for your own codebase using something like the cereal package:

import Data.Serialize (Serialize)
import qualified Data.Serialize as Serialize
instance {\-# OVERLAPPABLE #-\} (Typeable a, Serialize a) => Codec Binary a where
  encodingType _ _ = "binary/plain"
  encodePayload _ x = Serialize.encode x
  decode _ = Serialize.decode . inputPayloadData

Constructors

Binary 

Instances

Instances details
Show Binary Source # 
Instance details

Defined in Temporal.Payload

Eq Binary Source # 
Instance details

Defined in Temporal.Payload

Methods

(==) :: Binary -> Binary -> Bool #

(/=) :: Binary -> Binary -> Bool #

Lift Binary Source # 
Instance details

Defined in Temporal.Payload

Methods

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

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

Codec Binary ByteString Source # 
Instance details

Defined in Temporal.Payload

data Protobuf Source #

Constructors

Protobuf 

Instances

Instances details
Show Protobuf Source # 
Instance details

Defined in Temporal.Payload

Eq Protobuf Source # 
Instance details

Defined in Temporal.Payload

Lift Protobuf Source # 
Instance details

Defined in Temporal.Payload

Methods

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

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

Message a => Codec Protobuf a Source # 
Instance details

Defined in Temporal.Payload

data Zlib Source #

Constructors

Zlib 

Fields

applyPayloads :: ApplyPayloads codec args => codec -> Proxy args -> Proxy result -> (args :->: result) -> Vector Payload -> IO (Either String result) Source #

data Around base Source #

A codec that uses the base codec for actually encoding and decoding, but supports additional pre- and post-processing. This is useful for adding compression, encryption, or other transformations to an existing codec.

Constructors

Around 

Fields

Instances

Instances details
(Typeable a, Codec base a) => Codec (Around base) a Source # 
Instance details

Defined in Temporal.Payload

Methods

encoding :: Around base -> Proxy a -> ByteString Source #

messageType :: Around base -> a -> ByteString Source #

encode :: Around base -> a -> IO Payload Source #

decode :: Around base -> Payload -> IO (Either String a) Source #

data PayloadProcessor Source #

A codec that post-processes the payload after encoding and pre-processes before decoding.

Combining multiple PayloadProcessors will apply them in the order that they are added. For example, if you want to compress and then encrypt, you would add the compression processor first, then the encryption processor.

class ApplyPayloads codec (args :: [Type]) Source #

Minimal complete definition

applyPayloads

Instances

Instances details
ApplyPayloads codec ('[] :: [Type]) Source # 
Instance details

Defined in Temporal.Payload

Methods

applyPayloads :: codec -> Proxy ('[] :: [Type]) -> Proxy result -> (('[] :: [Type]) :->: result) -> Vector Payload -> IO (Either String result) Source #

(Codec codec ty, ApplyPayloads codec tys) => ApplyPayloads codec (ty ': tys) Source # 
Instance details

Defined in Temporal.Payload

Methods

applyPayloads :: codec -> Proxy (ty ': tys) -> Proxy result -> ((ty ': tys) :->: result) -> Vector Payload -> IO (Either String result) Source #

type family ArgsOf f :: [Type] where ... Source #

Equations

ArgsOf (arg -> rest) = arg ': ArgsOf rest 
ArgsOf _1 = '[] :: [Type] 

type family ResultOf (m :: Type -> Type) f where ... Source #

Equations

ResultOf m (_1 -> rest) = ResultOf m rest 
ResultOf m (m result) = result 
ResultOf m result = TypeError ((('Text "This function must use the (" ':<>: 'ShowType m) ':<>: 'Text ") monad.") ':$$: ('Text "Current type: " ':<>: 'ShowType result)) :: Type 

type family (args :: [Type]) :->: result where ... infixr 0 Source #

Construct a function type from a list of argument types and a result type.

Equations

('[] :: [Type]) :->: result = result 
(arg ': args) :->: result = arg -> args :->: result 

Vararg manipulation

class VarArgs (args :: [Type]) where Source #

Methods

sequenceArgs :: Monad m => Proxy (m result) -> m (args :->: m result) -> args :->: m result Source #

mapResult :: (result -> result') -> (args :->: result) -> args :->: result' Source #

foldlArgs :: AllArgs c args => Proxy c -> (forall a. c a => b -> a -> b) -> b -> args :->: b Source #

Instances

Instances details
VarArgs ('[] :: [Type]) Source # 
Instance details

Defined in Temporal.Payload

Methods

sequenceArgs :: Monad m => Proxy (m result) -> m (('[] :: [Type]) :->: m result) -> ('[] :: [Type]) :->: m result Source #

mapResult :: (result -> result') -> (('[] :: [Type]) :->: result) -> ('[] :: [Type]) :->: result' Source #

foldlArgs :: AllArgs c ('[] :: [Type]) => Proxy c -> (forall a. c a => b -> a -> b) -> b -> ('[] :: [Type]) :->: b Source #

VarArgs args => VarArgs (arg ': args) Source # 
Instance details

Defined in Temporal.Payload

Methods

sequenceArgs :: Monad m => Proxy (m result) -> m ((arg ': args) :->: m result) -> (arg ': args) :->: m result Source #

mapResult :: (result -> result') -> ((arg ': args) :->: result) -> (arg ': args) :->: result' Source #

foldlArgs :: AllArgs c (arg ': args) => Proxy c -> (forall a. c a => b -> a -> b) -> b -> (arg ': args) :->: b Source #

hoistResult :: forall {k} (args :: [Type]) (result :: k) m n. VarArgs args => (forall (x :: k). m x -> n x) -> (args :->: m result) -> args :->: n result Source #

foldMapArgs :: forall (args :: [Type]) c m. (VarArgs args, AllArgs c args, Monoid m) => (forall a. c a => a -> m) -> args :->: m Source #

foldMArgs :: forall (args :: [Type]) c b m. (VarArgs args, AllArgs c args, Monad m) => (forall a. c a => b -> a -> m b) -> b -> args :->: m b Source #

foldMArgs_ :: forall (args :: [Type]) c b m. (VarArgs args, AllArgs c args, Monad m) => (forall a. c a => b -> a -> m b) -> b -> args :->: m () Source #

withArgs :: forall (args :: [Type]) result codec. (VarArgs args, AllArgs (Codec codec) args) => codec -> (Vector UnencodedPayload -> result) -> args :->: result Source #

processorEncodePayloads :: (MonadIO m, Traversable f) => PayloadProcessor -> f Payload -> m (f Payload) Source #

This is the final step in the process of encoding payloads.

It takes a list of suspended payload encodings and runs them through the payload processor. This allows us to

type family AllArgs (c :: Type -> Constraint) (args :: [Type]) where ... Source #

Applies a constraint to all types in a type-level list.

Equations

AllArgs _1 ('[] :: [Type]) = () 
AllArgs c (arg ': args) = (c arg, AllArgs c args) 

type GatherArgs codec (args :: [Type]) = (VarArgs args, AllArgs (Codec codec) args) Source #

type GatherArgsOf codec f = GatherArgs codec (ArgsOf f) Source #

type FunctionSupportsCodec codec (args :: [Type]) result = (GatherArgs codec args, Codec codec result, Typeable result, ApplyPayloads codec args) Source #

type FunctionSupportsCodec' (m :: Type -> Type) codec f = (FunctionSupportsCodec codec (ArgsOf f) (ResultOf m f), f ~ (ArgsOf f :->: m (ResultOf m f))) Source #

data ValueError Source #

Used to denote that a payload either failed to encode or decode

Constructors

ValueError String