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

Faktory.Pool

Synopsis

Documentation

data FaktoryPool Source #

Since: 1.1.3.0

Instances

Instances details
HasFaktoryPool FaktoryPool Source # 
Instance details

Defined in Faktory.Pool

class HasFaktoryPool env where Source #

Since: 1.1.3.0

Instances

Instances details
HasFaktoryPool FaktoryPool Source # 
Instance details

Defined in Faktory.Pool

Pool Construction

data PoolSettings Source #

Since: 1.1.3.0

newFaktoryPool :: MonadIO m => Settings -> PoolSettings -> m FaktoryPool Source #

Build a FaktoryPool with the given settings

See Settings, envSettings, PoolSettings, and envPoolSettings.

Since: 1.1.3.0

Pool use

perform :: (MonadUnliftIO m, MonadReader env m, HasFaktoryPool env, ToJSON arg, HasCallStack) => JobOptions -> arg -> m JobId Source #

perform but using a Producer from the pool

Since: 1.1.3.0

buildJob :: (MonadUnliftIO m, MonadReader env m, HasFaktoryPool env) => JobOptions -> arg -> m (Job arg) Source #

buildJob but using a Producer from the pool

Since: 1.1.3.0

Direct access

withProducer :: (MonadUnliftIO m, MonadReader env m, HasFaktoryPool env) => (Producer -> m a) -> m a Source #

Acquire a Producer, use it, and return it to the pool

Since: 1.1.3.0

takeProducer :: (MonadIO m, MonadReader env m, HasFaktoryPool env) => m (Producer, m ()) Source #

Get a Producer from the pool along with an action to return it

You should prefer withProducer if at all possible. With this function you are responsible to ensure the return action is called (e.g. with finally).

This is only necessary if you are operating in a monad that doesn't have MonadUnliftIO (like ConduitT), so you need to take and return a Producer separately (e.g. with bracketP).

Since: 1.1.3.0

Re-exports

data Job arg Source #

Instances

Instances details
Foldable Job Source # 
Instance details

Defined in Faktory.Job

Methods

fold :: Monoid m => Job m -> m #

foldMap :: Monoid m => (a -> m) -> Job a -> m #

foldMap' :: Monoid m => (a -> m) -> Job a -> m #

foldr :: (a -> b -> b) -> b -> Job a -> b #

foldr' :: (a -> b -> b) -> b -> Job a -> b #

foldl :: (b -> a -> b) -> b -> Job a -> b #

foldl' :: (b -> a -> b) -> b -> Job a -> b #

foldr1 :: (a -> a -> a) -> Job a -> a #

foldl1 :: (a -> a -> a) -> Job a -> a #

toList :: Job a -> [a] #

null :: Job a -> Bool #

length :: Job a -> Int #

elem :: Eq a => a -> Job a -> Bool #

maximum :: Ord a => Job a -> a #

minimum :: Ord a => Job a -> a #

sum :: Num a => Job a -> a #

product :: Num a => Job a -> a #

Traversable Job Source # 
Instance details

Defined in Faktory.Job

Methods

traverse :: Applicative f => (a -> f b) -> Job a -> f (Job b) #

sequenceA :: Applicative f => Job (f a) -> f (Job a) #

mapM :: Monad m => (a -> m b) -> Job a -> m (Job b) #

sequence :: Monad m => Job (m a) -> m (Job a) #

Functor Job Source # 
Instance details

Defined in Faktory.Job

Methods

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

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

FromJSON args => FromJSON (Job args) Source # 
Instance details

Defined in Faktory.Job

Methods

parseJSON :: Value -> Parser (Job args) #

parseJSONList :: Value -> Parser [Job args] #

omittedField :: Maybe (Job args) #

ToJSON args => ToJSON (Job args) Source # 
Instance details

Defined in Faktory.Job

Methods

toJSON :: Job args -> Value #

toEncoding :: Job args -> Encoding #

toJSONList :: [Job args] -> Value #

toEncodingList :: [Job args] -> Encoding #

omitField :: Job args -> Bool #

Show arg => Show (Job arg) Source # 
Instance details

Defined in Faktory.Job

Methods

showsPrec :: Int -> Job arg -> ShowS #

show :: Job arg -> String #

showList :: [Job arg] -> ShowS #

data JobOptions Source #

Options for the execution of a job

These can be constructed using (<>):

let options = retry 1 <> jobtype MyJob

To enqueue with defaults, use mempty.

Options use Last semantics, so (e.g.) retry x <> will set retries to x only if not already set, and <> retry x will override any already-present retries to x.

Instances

Instances details
FromJSON JobOptions Source # 
Instance details

Defined in Faktory.JobOptions

Monoid JobOptions Source # 
Instance details

Defined in Faktory.JobOptions

Semigroup JobOptions Source # 
Instance details

Defined in Faktory.JobOptions

Generic JobOptions Source # 
Instance details

Defined in Faktory.JobOptions

Associated Types

type Rep JobOptions :: Type -> Type #

Show JobOptions Source # 
Instance details

Defined in Faktory.JobOptions

Eq JobOptions Source # 
Instance details

Defined in Faktory.JobOptions

type Rep JobOptions Source # 
Instance details

Defined in Faktory.JobOptions

once :: JobOptions Source #

Equivalent to retry (-1): no retries, and move to Dead on failure

newJob :: arg -> IO (Job arg) Source #

Construct a Job with default JobOptions

jobArg :: Job arg -> arg Source #