temporal-sdk-optimal-codec
Safe HaskellNone
LanguageHaskell2010

Temporal.Codec.Optimal

Synopsis

Documentation

data Composite (codecs :: [Type]) where Source #

The Composite codec allows you to combine multiple codecs into one.

The codecs are tried in order, and the first one that succeeds is used. If none of the codecs succeed, the compile-time error message will indicate the type that didn't satisfy any of the specified codecs.

This Codec is useful when you want to support multiple serialization formats and choose the best / most performant one for each type.

Note that this Codec relies upon the 'if-instance' package, which supplies a compiler plugin that allows us to use this. You must add the following pragma to the module that registers your workflow code:

{\-# OPTIONS_GHC -fplugin=IfSat.Plugin #-\}
-- ^ Put this at the top of the module that registers your workflow code.

let testFn :: Int -> Text -> Bool -> W.Workflow () () (Int, Text, Bool)
    testFn a b c = pure (a, b, c)
    wf = W.provideWorkflow defaultCodec "test" () testFn
    conf = configure () () $ do
      addWorkflow wf

If you forget to add this pragma, your code will fail to compile with a message like:

 hs-temporal/test/IntegrationSpec.hs:66:16: error:
    • No instance for (Codec Null ()
                       Data.Constraint.If.|| Codec
                                               (Temporal.Payload.Composite
                                                  '[Binary, Protobuf, JSON])
                                               ())
        arising from a use of ‘W.provideWorkflow’
    • In the expression:
        W.provideWorkflow defaultCodec "test" () testFn
      In an equation for ‘wf’:
          wf = W.provideWorkflow defaultCodec "test" () testFn
      In the expression:
        do taskQueue <- W.TaskQueue <$> uuidText
           let testFn :: W.Workflow () () ()
               testFn = pure ()
               ....
           withWorker conf
             $ do wfId <- uuidText
                  let ...
                  ....
   |
66 |           wf = W.provideWorkflow defaultCodec "test" () testFn
   |                ^^^^^^^^^^^^^^^^^

Constructors

CompositeNil :: Composite ('[] :: [Type]) 
CompositeCons :: forall codec (codecs1 :: [Type]). codec -> Composite codecs1 -> Composite (codec ': codecs1) 

Instances

Instances details
Codec fmt a || Codec (Composite codecs) a => Codec (Composite (fmt ': codecs)) a Source # 
Instance details

Defined in Temporal.Codec.Optimal

Methods

encoding :: Composite (fmt ': codecs) -> Proxy a -> ByteString #

messageType :: Composite (fmt ': codecs) -> a -> ByteString #

encode :: Composite (fmt ': codecs) -> a -> IO Payload #

decode :: Composite (fmt ': codecs) -> Payload -> IO (Either String a) #

(TypeError ('ShowType a ':<>: 'Text " is not supported by any of the provided codecs") :: Constraint) => Codec (Composite ('[] :: [Type])) a Source # 
Instance details

Defined in Temporal.Codec.Optimal

Methods

encoding :: Composite ('[] :: [Type]) -> Proxy a -> ByteString #

messageType :: Composite ('[] :: [Type]) -> a -> ByteString #

encode :: Composite ('[] :: [Type]) -> a -> IO Payload #

decode :: Composite ('[] :: [Type]) -> Payload -> IO (Either String a) #

class c || d where #

Methods

dispatch :: ((IsSat c ~ 'True, c) => r) -> ((IsSat c ~ 'False, IsSat d ~ 'True, d) => r) -> r #

ifSat :: IfSat ct => ((IsSat ct ~ 'True, ct) => r) -> (IsSat ct ~ 'False => r) -> r #

type IfSat ct = ct || () #

type family IsSat ct :: Bool where ... #