Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type TableName = Query
- pgEventName :: TableName -> Query
- newtype Seconds = Seconds {}
- delaySeconds :: MonadIO m => Seconds -> m ()
- oneSec :: Int
- data LogEvent
- data FailureMode
- data JobErrHandler a = Exception e => JobErrHandler (e -> Job -> FailureMode -> IO a)
- data ConcurrencyControl
- type JobId = Int
- data Status
- newtype JobRunnerName = JobRunnerName {}
- data Job = Job {}
- type JobRunner = Job -> IO ()
- data AllJobTypes
- data Config = Config {
- cfgTableName :: TableName
- cfgJobRunner :: Job -> IO ()
- cfgDefaultMaxAttempts :: Int
- cfgConcurrencyControl :: ConcurrencyControl
- cfgDbPool :: Pool Connection
- cfgPollingInterval :: Seconds
- cfgOnJobSuccess :: Job -> IO ()
- cfgOnJobFailed :: forall a. [JobErrHandler a]
- cfgOnJobStart :: Job -> IO ()
- cfgOnJobTimeout :: Job -> IO ()
- cfgPidFile :: Maybe FilePath
- cfgLogger :: LogLevel -> LogEvent -> IO ()
- cfgJobType :: Job -> Text
- cfgJobTypeSql :: Query
- cfgDefaultJobTimeout :: Seconds
- cfgJobToHtml :: [Job] -> IO [Html ()]
- cfgAllJobTypes :: AllJobTypes
Documentation
type TableName = Query Source #
An alias for Query
type. Since this type has an instance of IsString
you do not need to do anything special to create a value for this type. Just
ensure you have the OverloadedStrings
extention enabled. For example:
{-# LANGUAGE OverloadedStrings #-} myJobsTable :: TableName myJobsTable = "my_jobs"
pgEventName :: TableName -> Query Source #
delaySeconds :: MonadIO m => Seconds -> m () Source #
Convenience wrapper on-top of threadDelay
which takes Seconds
as an
argument, instead of micro-seconds.
LogJobStart !Job | Emitted when a job starts execution |
LogJobSuccess !Job !NominalDiffTime | Emitted when a job succeeds along with the time taken for execution. |
LogJobFailed !Job !SomeException !FailureMode !NominalDiffTime | Emitted when a job fails (but will be retried) along with the time taken for this attempt |
LogJobTimeout !Job | Emitted when a job times out and is picked-up again for execution |
LogPoll | Emitted whenever |
LogWebUIRequest | TODO |
LogText !Text | Emitted whenever any other event occurs |
Instances
data FailureMode Source #
Used by JobErrHandler
and LogEvent
to indicate the nature of failure.
FailWithRetry | |
FailPermanent | The job failed and will no longer be retried (probably because it has
been tried |
Instances
Eq FailureMode Source # | |
Defined in OddJobs.Types (==) :: FailureMode -> FailureMode -> Bool # (/=) :: FailureMode -> FailureMode -> Bool # | |
Show FailureMode Source # | |
Defined in OddJobs.Types showsPrec :: Int -> FailureMode -> ShowS # show :: FailureMode -> String # showList :: [FailureMode] -> ShowS # | |
Generic FailureMode Source # | |
Defined in OddJobs.Types type Rep FailureMode :: Type -> Type # from :: FailureMode -> Rep FailureMode x # to :: Rep FailureMode x -> FailureMode # | |
type Rep FailureMode Source # | |
data JobErrHandler a Source #
Exception handler for jobs. This is conceptually very similar to how
Handler
and catches
(from
Exception
) work in-tandem. Using cfgOnJobFailed
you can install
multiple exception handlers, where each handler is responsible for one type
of exception. OddJobs will execute the correct exception handler on the basis
of the type of runtime exception raised. For example:
cfgOnJobFailed = [ JobErrHandler $ (e :: HttpException) job failMode -> ... , JobErrHandler $ (e :: SqlException) job failMode -> ... , JobErrHandler $ (e :: ) job failMode -> ... ]
Note: Please refer to the section on alerts and
notifications
in the implementation guide to understand how to use the machinery provided
by JobErrHandler
and cfgOnJobFailed
.
Exception e => JobErrHandler (e -> Job -> FailureMode -> IO a) |
data ConcurrencyControl Source #
Note: Please read the section on controlling concurrency in the implementation guide to understand the implications of each option given by the data-type.
MaxConcurrentJobs Int | The maximum number of concurrent jobs that this instance of the job-runner can execute. |
UnlimitedConcurrentJobs | Not recommended: Please do not use this in production unless you know what you're doing. No machine can support unlimited concurrency. If your jobs are doing anything worthwhile, running a sufficiently large number concurrently is going to max-out some resource of the underlying machine, such as, CPU, memory, disk IOPS, or network bandwidth. |
DynamicConcurrency (IO Bool) | Use this to dynamically determine if the next job should be picked-up, or not. This is useful to write custom-logic to determine whether a limited resource is below a certain usage threshold (eg. CPU usage is below 80%). Caveat: This feature has not been tested in production, yet. |
Instances
Show ConcurrencyControl Source # | |
Defined in OddJobs.Types showsPrec :: Int -> ConcurrencyControl -> ShowS # show :: ConcurrencyControl -> String # showList :: [ConcurrencyControl] -> ShowS # |
Success | In the current version of odd-jobs you should not find any jobs having
the |
Queued | Jobs in |
Failed | Jobs in |
Retry | Jobs in |
Locked | Jobs in |
Instances
Bounded Status Source # | |
Enum Status Source # | |
Defined in OddJobs.Types | |
Eq Status Source # | |
Ord Status Source # | |
Show Status Source # | |
Generic Status Source # | |
ToJSON Status Source # | |
Defined in OddJobs.Types | |
FromJSON Status Source # | |
FromField Status Source # | |
Defined in OddJobs.Types | |
ToField Status Source # | |
Defined in OddJobs.Types | |
ToText Status Source # | |
Defined in OddJobs.Types | |
StringConv Text a => FromText (Either a Status) Source # | |
type Rep Status Source # | |
Defined in OddJobs.Types type Rep Status = D1 (MetaData "Status" "OddJobs.Types" "odd-jobs-0.2.2-IQT5Y8dLVtd1UwbOhFLeU6" False) ((C1 (MetaCons "Success" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Queued" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Failed" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Retry" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Locked" PrefixI False) (U1 :: Type -> Type)))) |
newtype JobRunnerName Source #
Instances
Job | |
|
Instances
data AllJobTypes Source #
The web/admin UI needs to know a "master list" of all job-types to be
able to power the "filter by job-type" feature. This data-type helps in
letting odd-jobs know how to get such a master-list. The function specified
by this type is run once when the job-runner starts (and stored in an
internal IORef
). After that the list of job-types needs to be updated
manually by pressing the appropriate "refresh" link in the admin/web UI.
AJTFixed [Text] | A fixed-list of job-types. If you don't want to increase boilerplate,
consider using |
AJTSql (Connection -> IO [Text]) | Construct the list of job-types dynamically by looking at the actual
payloads in |
AJTCustom (IO [Text]) | A custom |
While odd-jobs is highly configurable and the Config
data-type might seem
daunting at first, it is not necessary to tweak every single configuration
parameter by hand.
Recommendation: Please start-off by building a Config
by using the
mkConfig
function (to get something with sensible
defaults) and then tweaking config parameters on a case-by-case basis.
Config | |
|