Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data CheckStatus
- data CheckResult
- data NagiosPlugin a
- runNagiosPlugin :: NagiosPlugin a -> IO ()
- runNagiosPlugin' :: NagiosPlugin a -> IO (a, CheckState)
- addPerfDatum :: Text -> PerfValue -> UOM -> Maybe PerfValue -> Maybe PerfValue -> Maybe PerfValue -> Maybe PerfValue -> NagiosPlugin ()
- addPerfData :: ToPerfData a => a -> NagiosPlugin ()
- addBarePerfDatum :: Text -> PerfValue -> UOM -> NagiosPlugin ()
- addResult :: CheckStatus -> Text -> NagiosPlugin ()
- checkStatus :: CheckResult -> CheckStatus
- checkInfo :: CheckResult -> Text
- worstResult :: [CheckResult] -> CheckResult
- finishState :: CheckState -> (CheckStatus, Text)
- data Range
- data UOM :: *
- = Second
- | Millisecond
- | Microsecond
- | Percent
- | Byte
- | Kilobyte
- | Megabyte
- | Gigabyte
- | Terabyte
- | Counter
- | NullUnit
- | UnknownUOM
- data PerfValue
- data PerfDatum = PerfDatum {}
- class ToPerfData a where
- toPerfData :: a -> [PerfDatum]
- barePerfDatum :: Text -> PerfValue -> UOM -> PerfDatum
Documentation
data CheckStatus Source
Nagios plugin exit statuses. Ordered by priority -
OK
< Warning
< Critical
< Unknown
, which correspond to plugin exit
statuses of 0, 1, 2, and 3 respectively.
data CheckResult Source
A CheckResult is the exit status of the plugin combined with the
plugin's info text. A NagiosPlugin
which exits with
CheckResult (Critical "entropy decreasing in closed system")
as its peak-badness CheckResult (and no PerfDatum
s) will a) exit with
status 2 and b) output the text "CRITICAL: entropy decreasing in closed
system".
data NagiosPlugin a Source
runNagiosPlugin :: NagiosPlugin a -> IO () Source
Execute a Nagios check. The program will terminate at the check's completion. A default status will provided if none is given.
runNagiosPlugin' :: NagiosPlugin a -> IO (a, CheckState) Source
Execute a Nagios check as with runNagiosPlugin
, but return its
final state rather than terminating.
:: Text | Name of the quantity being measured. |
-> PerfValue | Measured value. |
-> UOM | Unit of the measured value. |
-> Maybe PerfValue | Minimum threshold. |
-> Maybe PerfValue | Maximum threshold. |
-> Maybe PerfValue | Warning threshold. |
-> Maybe PerfValue | Critical threshold. |
-> NagiosPlugin () |
Insert a performance metric into the list the check will output.
addPerfData :: ToPerfData a => a -> NagiosPlugin () Source
Alternative mechanism for adding perfdata generated from complex
types; just implement the toPerfData
typeclass.
:: Text | Name of the quantity being measured. |
-> PerfValue | Measured value. |
-> UOM | Unit of the measured value. |
-> NagiosPlugin () |
Convenience function to insert a perfdatum without thresholds for min, max, warn or crit. Note that unless the range of the metric is actually unbounded, specifying explicit thresholds is considered good practice (it makes life easier for authors of graphing packages).
FIXME: implement thresholds properly and default to negative and positive infinity for min and max here.
addResult :: CheckStatus -> Text -> NagiosPlugin () Source
Insert a result. Only the CheckStatus
with the most badness
will determine the check's exit status.
checkStatus :: CheckResult -> CheckStatus Source
Extract the return status from a CheckResult
.
checkInfo :: CheckResult -> Text Source
Extract the infotext from a CheckResult
.
worstResult :: [CheckResult] -> CheckResult Source
Returns result with greatest badness, or a default UNKNOWN result if no results have been specified.
finishState :: CheckState -> (CheckStatus, Text) Source
Given a check's final state, return the status and output it would exit with.
A Range
is a combination of a lower boundary and an upper boundary (x,y).
An AcceptableRange
asserts that measured values between x and y
imply that nothing is wrong; an UnacceptableRange implies the inverse.
data UOM :: *
Nagios unit of measurement. NullUnit is an empty string in the check result; UnknownUOM indicates a failure to parse.
Value of a performance metric.
One performance metric. A plugin will output zero or more of these,
whereupon Nagios generally passes them off to an external system such
as RRDTool or
Vaultaire.
The thresholds are purely informative (designed to be graphed), and
do not affect alerting; likewise with _min
and _max
.
PerfDatum | |
|
class ToPerfData a where Source
toPerfData :: a -> [PerfDatum] Source