module System.Nagios.Plugin.Check
(
CheckStatus(..),
CheckResult,
NagiosPlugin,
runNagiosPlugin,
runNagiosPlugin',
addPerfDatum,
addPerfData,
addBarePerfDatum,
addResult,
checkStatus,
checkInfo,
worstResult,
finishState
) where
import Control.Applicative
import qualified Control.Monad.Catch as E
import Control.Monad.State.Lazy
import Data.Bifunctor
import Data.Monoid
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.IO as T
import System.Exit
import System.Nagios.Plugin.PerfData
data CheckStatus = OK
| Warning
| Critical
| Unknown
deriving (Enum, Eq, Ord)
instance Show CheckStatus where
show OK = "OK"
show Warning = "WARNING"
show Critical = "CRITICAL"
show Unknown = "UNKNOWN"
newtype CheckResult = CheckResult
{ unCheckResult :: (CheckStatus, Text) }
deriving (Eq, Ord, Show)
checkStatus :: CheckResult -> CheckStatus
checkStatus = fst . unCheckResult
checkInfo :: CheckResult -> Text
checkInfo = snd . unCheckResult
type CheckState = ([CheckResult], [PerfDatum])
newtype NagiosPlugin a = NagiosPlugin
{
unNagiosPlugin :: StateT CheckState IO a
} deriving (Functor, Applicative, Monad, MonadIO, MonadState CheckState, E.MonadCatch, E.MonadThrow)
runNagiosPlugin :: NagiosPlugin a -> IO ()
runNagiosPlugin check = do
(_, st) <- runNagiosPlugin' $ E.catch check panic
finishWith st
where
panic :: E.SomeException -> NagiosPlugin a
panic = liftIO . finishWith . panicState
runNagiosPlugin' :: NagiosPlugin a -> IO (a, CheckState)
runNagiosPlugin' a = runStateT (unNagiosPlugin a) mempty
addResult :: CheckStatus -> Text -> NagiosPlugin ()
addResult s t =
modify (first (CheckResult (s, t) :))
addPerfDatum ::
Text
-> PerfValue
-> UOM
-> Maybe PerfValue
-> Maybe PerfValue
-> Maybe PerfValue
-> Maybe PerfValue
-> NagiosPlugin ()
addPerfDatum info val uom min' max' warn crit =
modify (second (PerfDatum info val uom min' max' warn crit :))
addBarePerfDatum ::
Text
-> PerfValue
-> UOM
-> NagiosPlugin ()
addBarePerfDatum info val uom =
addPerfDatum info val uom Nothing Nothing Nothing Nothing
addPerfData ::
ToPerfData a
=> a
-> NagiosPlugin ()
addPerfData pd = modify (second (++ toPerfData pd))
defaultResult :: CheckResult
defaultResult = CheckResult (Unknown, T.pack "no check result specified")
panicState :: E.SomeException -> CheckState
panicState = (,[]) . return . CheckResult . panicResult
where
panicResult e = (Critical,
T.pack ("unhandled exception: " ++ show e))
worstResult :: [CheckResult] -> CheckResult
worstResult rs
| null rs = defaultResult
| otherwise = maximum rs
fmtPerfData :: [PerfDatum] -> Text
fmtPerfData = T.intercalate " " . map fmtPerfDatum
where
fmtPerfDatum PerfDatum{..} = T.concat
[ _label
, "="
, T.pack (show _value)
, T.pack (show _uom)
, fmtThreshold _warn
, fmtThreshold _crit
, fmtThreshold _min
, fmtThreshold _max
]
fmtThreshold Nothing = ";"
fmtThreshold (Just t) = T.pack $ ";" <> show t
fmtResults :: [CheckResult] -> Text
fmtResults = fmtResult . worstResult
where
fmtResult (CheckResult (s,t)) =
T.pack (show s) <> ": " <> t
finishState :: CheckState -> (CheckStatus, Text)
finishState (rs, pds) =
let worst = worstResult rs
output = fmtResults rs <> perfdataPart pds
in (checkStatus worst, output)
where
perfdataPart [] = ""
perfdataPart xs = " | " <> fmtPerfData xs
finishWith :: MonadIO m => CheckState -> m a
finishWith = liftIO . exitWithStatus . finishState
exitWithStatus :: (CheckStatus, Text) -> IO a
exitWithStatus (OK, t) = T.putStrLn t >> exitSuccess
exitWithStatus (r, t) = T.putStrLn t >> exitWith (ExitFailure $ fromEnum r)