faktory-1.1.2.4: Faktory Worker for Haskell
Safe HaskellSafe-Inferred
LanguageHaskell2010

Faktory.Ent.Batch

Description

Support for the BATCH command (Enterprise only)

https://github.com/contribsys/faktory/wiki/Ent-Batches

Batches allow multiple Jobs to be enqueued as a group, with a description (visible in the admin UI) and Jobs attached to run on completion of all Jobs within the group (always, or only if all were successful).

Usage:

-- Build a Job to run at completion of the Batch. Arguments are the same as
-- you would pass to perform the Job.
onComplete <- buildJob mempty producer myJob

runBatch (complete onComplete <> description "My Batch") producer $ do
  -- Use batchPerform instead of perform
  void $ batchPerform mempty producer myBatchedJob1
  void $ batchPerform mempty producer myBatchedJob2

/NOTE: This module does not support batched Jobs dynamically adding more Jobs to the Batch. PRs welcome.

Synopsis

Options

data BatchOptions arg Source #

Instances

Instances details
ToJSON arg => ToJSON (BatchOptions arg) Source # 
Instance details

Defined in Faktory.Ent.Batch

Monoid (BatchOptions arg) Source # 
Instance details

Defined in Faktory.Ent.Batch

Semigroup (BatchOptions arg) Source # 
Instance details

Defined in Faktory.Ent.Batch

Methods

(<>) :: BatchOptions arg -> BatchOptions arg -> BatchOptions arg #

sconcat :: NonEmpty (BatchOptions arg) -> BatchOptions arg #

stimes :: Integral b => b -> BatchOptions arg -> BatchOptions arg #

Generic (BatchOptions arg) Source # 
Instance details

Defined in Faktory.Ent.Batch

Associated Types

type Rep (BatchOptions arg) :: Type -> Type #

Methods

from :: BatchOptions arg -> Rep (BatchOptions arg) x #

to :: Rep (BatchOptions arg) x -> BatchOptions arg #

type Rep (BatchOptions arg) Source # 
Instance details

Defined in Faktory.Ent.Batch

type Rep (BatchOptions arg) = D1 ('MetaData "BatchOptions" "Faktory.Ent.Batch" "faktory-1.1.2.4-H1ZchBbHWdLEA0FaTGZZJf" 'False) (C1 ('MetaCons "BatchOptions" 'PrefixI 'True) (S1 ('MetaSel ('Just "boDescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Last Text))) :*: (S1 ('MetaSel ('Just "boSuccess") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Last (Job arg)))) :*: S1 ('MetaSel ('Just "boComplete") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Last (Job arg)))))))

Running

runBatch :: ToJSON arg => BatchOptions arg -> Producer -> Batch a -> IO a Source #

data Batch a Source #

Instances

Instances details
MonadIO Batch Source # 
Instance details

Defined in Faktory.Ent.Batch

Methods

liftIO :: IO a -> Batch a #

Applicative Batch Source # 
Instance details

Defined in Faktory.Ent.Batch

Methods

pure :: a -> Batch a #

(<*>) :: Batch (a -> b) -> Batch a -> Batch b #

liftA2 :: (a -> b -> c) -> Batch a -> Batch b -> Batch c #

(*>) :: Batch a -> Batch b -> Batch b #

(<*) :: Batch a -> Batch b -> Batch a #

Functor Batch Source # 
Instance details

Defined in Faktory.Ent.Batch

Methods

fmap :: (a -> b) -> Batch a -> Batch b #

(<$) :: a -> Batch b -> Batch a #

Monad Batch Source # 
Instance details

Defined in Faktory.Ent.Batch

Methods

(>>=) :: Batch a -> (a -> Batch b) -> Batch b #

(>>) :: Batch a -> Batch b -> Batch b #

return :: a -> Batch a #

MonadReader BatchId Batch Source # 
Instance details

Defined in Faktory.Ent.Batch

Methods

ask :: Batch BatchId #

local :: (BatchId -> BatchId) -> Batch a -> Batch a #

reader :: (BatchId -> a) -> Batch a #

Low-level

newtype BatchId Source #

Constructors

BatchId Text 

Instances

Instances details
FromJSON BatchId Source # 
Instance details

Defined in Faktory.Ent.Batch

ToJSON BatchId Source # 
Instance details

Defined in Faktory.Ent.Batch

Show BatchId Source # 
Instance details

Defined in Faktory.Ent.Batch

Eq BatchId Source # 
Instance details

Defined in Faktory.Ent.Batch

Methods

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

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

MonadReader BatchId Batch Source # 
Instance details

Defined in Faktory.Ent.Batch

Methods

ask :: Batch BatchId #

local :: (BatchId -> BatchId) -> Batch a -> Batch a #

reader :: (BatchId -> a) -> Batch a #

newtype CustomBatchId Source #

Constructors

CustomBatchId 

Fields

Instances

Instances details
ToJSON CustomBatchId Source # 
Instance details

Defined in Faktory.Ent.Batch

Generic CustomBatchId Source # 
Instance details

Defined in Faktory.Ent.Batch

Associated Types

type Rep CustomBatchId :: Type -> Type #

type Rep CustomBatchId Source # 
Instance details

Defined in Faktory.Ent.Batch

type Rep CustomBatchId = D1 ('MetaData "CustomBatchId" "Faktory.Ent.Batch" "faktory-1.1.2.4-H1ZchBbHWdLEA0FaTGZZJf" 'True) (C1 ('MetaCons "CustomBatchId" 'PrefixI 'True) (S1 ('MetaSel ('Just "bid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BatchId)))