ngx-export-healthcheck-1.6.3: Active health checks and monitoring of Nginx upstreams
Copyright(c) Alexey Radkov 2022-2024
LicenseBSD-style
Maintaineralexey.radkov@gmail.com
Stabilitystable
Portabilitynon-portable (requires Template Haskell)
Safe HaskellSafe-Inferred
LanguageHaskell2010

NgxExport.Healthcheck

Description

Active health checks and monitoring of Nginx upstreams.

Synopsis

Type declarations

type ServiceKey = Text Source #

Custom service key.

type Upstream = Text Source #

Upstream name.

type PeerName = Text Source #

Peer name (actually, IP address of the peer).

type PeerHostName = Text Source #

Peer host name (normally, FQDN).

type Peer = (PeerName, PeerHostName) Source #

Peer identifier.

type Peers = [Peer] Source #

List of peers.

type FlatPeers = [PeerName] Source #

List of peers without host names.

type AnnotatedFlatPeers = [(UTCTime, PeerName)] Source #

List of peers without host names annotated by timestamps.

type MUpstream a = Map Upstream a Source #

Map over Upstream keys.

type MServiceKey a = Map ServiceKey (MUpstream a) Source #

Map over ServiceKey keys with values of an MUpstream type instance.

Use a custom CA store

useCustomCAStore :: CertificateStore -> IO () Source #

Use a custom CA store in health checks over https.

When doing health checks over https, it's sometimes required to tweak the location of the trusted certificates store. This function implements such a tweak when it's run from the initialization hook.

Example 1: use a CA store accessible in Nginx worker processes

Expand
File ngx_healthcheck.hs
{-# LANGUAGE TemplateHaskell #-}

module NgxHealthcheck where

import           NgxExport
import           NgxExport.Healthcheck
import           System.Environment
import           Data.Maybe
import           Data.X509.CertificateStore

customCAStore :: IO ()
customCAStore = do
    args <- dropWhile (/= "--ca") <$> getArgs
    case args of
        _ : ca : _ -> do
            store <- fromJust <$> readCertificateStore ca
            store `seq` useCustomCAStore store
        _ -> return ()
ngxExportInitHook 'customCAStore
File nginx.conf (a fragment)
    haskell program_options --ca /path/to/ca-dir-or-file;
    haskell load /var/lib/nginx/ngx_healthcheck.so;

Example 2: use a CA store accessible only in Nginx master process

Expand

In this case, the mread trick is used to make Nginx master process substitute the file content in place of the path contained in the argument of haskell program_options which follows --mread:ca.

File ngx_healthcheck.hs
{-# LANGUAGE TemplateHaskell #-}

module NgxHealthcheck where

import           NgxExport
import           NgxExport.Healthcheck
import           Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as C8
import           System.Environment
import           Data.Maybe
import           Data.Either
import           Data.X509
import           Data.X509.CertificateStore
import           Data.PEM

mkCertificateStore :: ByteString -> Maybe CertificateStore
mkCertificateStore ca = do
    parsed <- either (return Nothing) (Just . rights . map getCert) $
        pemParseBS ca
    Just $ makeCertificateStore parsed
    where getCert = decodeSignedCertificate . pemContent

customCAStore :: IO ()
customCAStore = do
    args <- dropWhile (/= "--mread:ca") <$> getArgs
    case args of
        _ : ca : _ -> do
            let store = fromJust $ mkCertificateStore $ C8.pack ca
            store `seq` useCustomCAStore store
        _ -> return ()
ngxExportInitHook 'customCAStore
File nginx.conf (a fragment)
    haskell program_options --mread:ca /path/to/ca-file;
    haskell load /var/lib/nginx/ngx_healthcheck.so;

Since: 1.6.3