job-0.1: Job queue
Safe HaskellSafe-Inferred
LanguageGHC2021

Job

Synopsis

Queue

data Queue job Source #

A job Queue.

  • jobs can be pushed to the Queue for eventual execution, pulled from the Queue for immediate execution, and the Queue itself can be pruned.
  • Job.Memory.queue is an in-memory implementation that can serve as reference.
  • Other backends are expected to provide a Queue implementation.

Constructors

Queue 

Fields

  • push :: Nice -> UTCTime -> job -> IO Id

    Push new job to the queue so to be executed after the specified UTCTime, which may be in the past. Throws if the Queue has already been released.

  • pull :: Acquire (Maybe (Work job))

    Pull some Work from the queue

  • prune :: forall a. Monoid a => (Id -> Meta -> job -> (Bool, a)) -> IO a

    Prune jobs from the Queue, keeping only those for which the given function returns True (like filter). Allows collecting some additional Monoidal output. The given jobs are in no particular order. Throws if the Queue has already been released. IMPORTANT: If you remove a job that is currently active, it might be pushed back to the Queue later if required by retry or a Work exception.

push :: forall job m. MonadIO m => Queue job -> Nice -> UTCTime -> job -> m Id Source #

Like the push field in Queue, except with a bit more polymorphic type and intended to be used as a top-level function.

prune :: forall job a m. (Monoid a, MonadIO m) => Queue job -> (Id -> Meta -> job -> (Bool, a)) -> m a Source #

Like the prune field in Queue, except with a bit more polymorphic type and intended to be used as a top-level function.

Work

data Work job Source #

A job together with its Queue execution context details.

As soon as you get your hands on a Work, which you do through pull, start working on it right away.

Constructors

Work 

Fields

Instances

Instances details
Functor Work Source # 
Instance details

Defined in Job

Methods

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

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

retry :: forall job m. MonadIO m => Work job -> Nice -> UTCTime -> m () Source #

Like the retry field in Work, except with a bit more polymorphic type and intended to be used as a top-level function.

finish :: forall job m. MonadIO m => Work job -> m () Source #

Like the finish field in Work, except with a bit more polymorphic type and intended to be used as a top-level function.

Meta

data Meta Source #

Wrapper for all the job-related data accessible through Queue's prune function.

Constructors

Meta 

Fields

  • alive :: Maybe UTCTime

    If Just, the job is currently being Worked on, allegedly. The last time the job sent a heartbeat is attached.

  • nice :: Nice

    Nice value used while scheduling the job.

  • wait :: UTCTime

    Time until the Queue is or was supposed to wait before considering working on the job.

  • try :: Word32

    How many tries have been attempted already (excluding the current one, in case alive is Just).

Instances

Instances details
Show Meta Source # 
Instance details

Defined in Job

Methods

showsPrec :: Int -> Meta -> ShowS #

show :: Meta -> String #

showList :: [Meta] -> ShowS #

Eq Meta Source # 
Instance details

Defined in Job

Methods

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

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

Ord Meta Source #

Order compatible with the one in prune.

Instance details

Defined in Job

Methods

compare :: Meta -> Meta -> Ordering #

(<) :: Meta -> Meta -> Bool #

(<=) :: Meta -> Meta -> Bool #

(>) :: Meta -> Meta -> Bool #

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

max :: Meta -> Meta -> Meta #

min :: Meta -> Meta -> Meta #

Id

data Id Source #

Unique identifier for the scheduled job (and re-scheduled job, see pull and retry).

Instances

Instances details
Show Id Source # 
Instance details

Defined in Job

Methods

showsPrec :: Int -> Id -> ShowS #

show :: Id -> String #

showList :: [Id] -> ShowS #

Eq Id Source # 
Instance details

Defined in Job

Methods

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

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

Ord Id Source # 
Instance details

Defined in Job

Methods

compare :: Id -> Id -> Ordering #

(<) :: Id -> Id -> Bool #

(<=) :: Id -> Id -> Bool #

(>) :: Id -> Id -> Bool #

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

max :: Id -> Id -> Id #

min :: Id -> Id -> Id #

Hashable Id Source # 
Instance details

Defined in Job

Methods

hashWithSalt :: Int -> Id -> Int #

hash :: Id -> Int #

HasField "uuid7" Id UUID Source # 
Instance details

Defined in Job

Methods

getField :: Id -> UUID #

newId :: MonadIO m => m Id Source #

Nice

newtype Nice Source #

Nice value for a job.

  • The lower the value, the less “nice” a job is to other jobs. Meaning it will have priority over other jobs, and possibly be allocated more resources.
  • The higher the value, the “nicer” a job is to other jobs. Meaning it will have less priority over other jobs, and possibly allow competing jobs to take more resources.
  • Use nice0 (i.e,. Nice 0) as default Nice value.

Constructors

Nice 

Fields

Instances

Instances details
Bounded Nice Source # 
Instance details

Defined in Job

Enum Nice Source # 
Instance details

Defined in Job

Methods

succ :: Nice -> Nice #

pred :: Nice -> Nice #

toEnum :: Int -> Nice #

fromEnum :: Nice -> Int #

enumFrom :: Nice -> [Nice] #

enumFromThen :: Nice -> Nice -> [Nice] #

enumFromTo :: Nice -> Nice -> [Nice] #

enumFromThenTo :: Nice -> Nice -> Nice -> [Nice] #

Show Nice Source # 
Instance details

Defined in Job

Methods

showsPrec :: Int -> Nice -> ShowS #

show :: Nice -> String #

showList :: [Nice] -> ShowS #

Eq Nice Source # 
Instance details

Defined in Job

Methods

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

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

Ord Nice Source # 
Instance details

Defined in Job

Methods

compare :: Nice -> Nice -> Ordering #

(<) :: Nice -> Nice -> Bool #

(<=) :: Nice -> Nice -> Bool #

(>) :: Nice -> Nice -> Bool #

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

max :: Nice -> Nice -> Nice #

min :: Nice -> Nice -> Nice #