Safe Haskell | None |
---|---|
Language | Haskell2010 |
Temporal.Payload
Contents
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
- data Payload = Payload {}
- class Codec fmt a where
- encoding :: fmt -> Proxy a -> ByteString
- messageType :: fmt -> a -> ByteString
- encode :: fmt -> a -> IO Payload
- decode :: fmt -> Payload -> IO (Either String a)
- data JSON = JSON
- data Null = Null
- data Binary = Binary
- data Protobuf = Protobuf
- data Zlib = Zlib {}
- zlib :: Zlib
- applyPayloads :: ApplyPayloads codec args => codec -> Proxy args -> Proxy result -> (args :->: result) -> Vector Payload -> IO (Either String result)
- data Around base = Around {
- around :: PayloadProcessor
- baseCodec :: base
- mkPayloadProcessor :: Codec fmt Payload => fmt -> PayloadProcessor
- addPayloadProcessor :: Codec fmt Payload => fmt -> PayloadProcessor -> PayloadProcessor
- data PayloadProcessor = PayloadProcessor {
- payloadProcessorEncode :: Payload -> IO Payload
- payloadProcessorDecode :: Payload -> IO (Either String Payload)
- class ApplyPayloads codec (args :: [Type])
- type family ArgsOf f :: [Type] where ...
- type family ResultOf (m :: Type -> Type) f where ...
- type family (args :: [Type]) :->: result where ...
- convertToProtoPayload :: Payload -> Payload
- convertFromProtoPayload :: Payload -> Payload
- class VarArgs (args :: [Type]) where
- hoistResult :: forall {k} (args :: [Type]) (result :: k) m n. VarArgs args => (forall (x :: k). m x -> n x) -> (args :->: m result) -> args :->: n result
- foldMapArgs :: forall (args :: [Type]) c m. (VarArgs args, AllArgs c args, Monoid m) => (forall a. c a => a -> m) -> args :->: m
- 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
- 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 ()
- withArgs :: forall (args :: [Type]) result codec. (VarArgs args, AllArgs (Codec codec) args) => codec -> (Vector UnencodedPayload -> result) -> args :->: result
- type UnencodedPayload = IO Payload
- processorEncodePayloads :: (MonadIO m, Traversable f) => PayloadProcessor -> f Payload -> m (f Payload)
- processorDecodePayloads :: (MonadIO m, Traversable f) => PayloadProcessor -> f Payload -> m (f Payload)
- type family AllArgs (c :: Type -> Constraint) (args :: [Type]) where ...
- type GatherArgs codec (args :: [Type]) = (VarArgs args, AllArgs (Codec codec) args)
- type GatherArgsOf codec f = GatherArgs codec (ArgsOf f)
- type FunctionSupportsCodec codec (args :: [Type]) result = (GatherArgs codec args, Codec codec result, Typeable result, ApplyPayloads codec args)
- type FunctionSupportsCodec' (m :: Type -> Type) codec f = (FunctionSupportsCodec codec (ArgsOf f) (ResultOf m f), f ~ (ArgsOf f :->: m (ResultOf m f)))
- data ValueError = ValueError String
Documentation
Constructors
Payload | |
Fields |
class Codec fmt a where Source #
We want to be able to serialize & deserialize the parameters of a function using an arbitrary serialization format.
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 #
Instances
Codec Binary ByteString Source # | |
Defined in Temporal.Payload Methods encoding :: Binary -> Proxy ByteString -> ByteString Source # messageType :: Binary -> ByteString -> ByteString Source # encode :: Binary -> ByteString -> IO Payload Source # decode :: Binary -> Payload -> IO (Either String ByteString) Source # | |
(Typeable a, ToJSON a, FromJSON a) => Codec JSON a Source # | |
Codec Null () Source # | |
Message a => Codec Protobuf a Source # | |
Codec Zlib Payload Source # | |
(Typeable a, Codec base a) => Codec (Around base) a Source # | |
Constructors
JSON |
Constructors
Null |
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
Show Binary Source # | |
Eq Binary Source # | |
Lift Binary Source # | |
Codec Binary ByteString Source # | |
Defined in Temporal.Payload Methods encoding :: Binary -> Proxy ByteString -> ByteString Source # messageType :: Binary -> ByteString -> ByteString Source # encode :: Binary -> ByteString -> IO Payload Source # decode :: Binary -> Payload -> IO (Either String ByteString) Source # |
Constructors
Protobuf |
Constructors
Zlib | |
Fields
|
applyPayloads :: ApplyPayloads codec args => codec -> Proxy args -> Proxy result -> (args :->: result) -> Vector Payload -> IO (Either String result) 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
|
mkPayloadProcessor :: Codec fmt Payload => fmt -> PayloadProcessor Source #
addPayloadProcessor :: Codec fmt Payload => fmt -> PayloadProcessor -> PayloadProcessor Source #
data PayloadProcessor Source #
A codec that post-processes the payload after encoding and pre-processes before decoding.
Combining multiple PayloadProcessor
s 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.
Constructors
PayloadProcessor | |
Fields
|
class ApplyPayloads codec (args :: [Type]) Source #
Minimal complete definition
Instances
ApplyPayloads codec ('[] :: [Type]) Source # | |
(Codec codec ty, ApplyPayloads codec tys) => ApplyPayloads codec (ty ': tys) Source # | |
type family (args :: [Type]) :->: result where ... infixr 0 Source #
Construct a function type from a list of argument types and a result type.
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
VarArgs ('[] :: [Type]) Source # | |
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 # | |
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 #
type UnencodedPayload = IO Payload 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
processorDecodePayloads :: (MonadIO m, Traversable f) => PayloadProcessor -> f Payload -> m (f Payload) Source #
type family AllArgs (c :: Type -> Constraint) (args :: [Type]) where ... Source #
Applies a constraint to all types in a type-level list.
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 |
Instances
Exception ValueError Source # | |
Defined in Temporal.Payload Methods toException :: ValueError -> SomeException # fromException :: SomeException -> Maybe ValueError # displayException :: ValueError -> String # backtraceDesired :: ValueError -> Bool # | |
Show ValueError Source # | |
Defined in Temporal.Payload Methods showsPrec :: Int -> ValueError -> ShowS # show :: ValueError -> String # showList :: [ValueError] -> ShowS # | |
Eq ValueError Source # | |
Defined in Temporal.Payload |