Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data FaktoryPool
- class HasFaktoryPool env where
- faktoryPoolL :: Lens' env FaktoryPool
- data Settings
- data PoolSettings
- newFaktoryPool :: MonadIO m => Settings -> PoolSettings -> m FaktoryPool
- perform :: (MonadUnliftIO m, MonadReader env m, HasFaktoryPool env, ToJSON arg, HasCallStack) => JobOptions -> arg -> m JobId
- buildJob :: (MonadUnliftIO m, MonadReader env m, HasFaktoryPool env) => JobOptions -> arg -> m (Job arg)
- withProducer :: (MonadUnliftIO m, MonadReader env m, HasFaktoryPool env) => (Producer -> m a) -> m a
- takeProducer :: (MonadIO m, MonadReader env m, HasFaktoryPool env) => m (Producer, m ())
- data Job arg
- data JobOptions
- type JobId = String
- once :: JobOptions
- retry :: Int -> JobOptions
- at :: UTCTime -> JobOptions
- queue :: Queue -> JobOptions
- custom :: ToJSON a => a -> JobOptions
- reserveFor :: Natural -> JobOptions
- jobtype :: String -> JobOptions
- in_ :: NominalDiffTime -> JobOptions
- newJob :: arg -> IO (Job arg)
- jobArg :: Job arg -> arg
- jobRetriesRemaining :: Job arg -> Int
- jobReserveForMicroseconds :: Job arg -> Int
Documentation
data FaktoryPool Source #
Since: 1.1.3.0
Instances
HasFaktoryPool FaktoryPool Source # | |
Defined in Faktory.Pool |
class HasFaktoryPool env where Source #
Since: 1.1.3.0
faktoryPoolL :: Lens' env FaktoryPool Source #
Instances
HasFaktoryPool FaktoryPool Source # | |
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 #
buildJob :: (MonadUnliftIO m, MonadReader env m, HasFaktoryPool env) => JobOptions -> arg -> m (Job arg) Source #
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
Instances
Foldable Job Source # | |
Defined in Faktory.Job 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 # elem :: Eq a => a -> Job a -> Bool # maximum :: Ord a => Job a -> a # | |
Traversable Job Source # | |
Functor Job Source # | |
FromJSON args => FromJSON (Job args) Source # | |
Defined in Faktory.Job | |
ToJSON args => ToJSON (Job args) Source # | |
Show arg => Show (Job arg) Source # | |
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.)
will set retries to
retry
x <>x
only if not already set, and <>
will override any
already-present retries to retry
xx
.
Instances
once :: JobOptions Source #
Equivalent to
: no retries, and move to Dead on failureretry
(-1)
retry :: Int -> JobOptions Source #
at :: UTCTime -> JobOptions Source #
queue :: Queue -> JobOptions Source #
custom :: ToJSON a => a -> JobOptions Source #
reserveFor :: Natural -> JobOptions Source #
jobtype :: String -> JobOptions Source #
in_ :: NominalDiffTime -> JobOptions Source #
jobRetriesRemaining :: Job arg -> Int Source #
jobReserveForMicroseconds :: Job arg -> Int Source #