{-# LANGUAGE CPP #-} -- | This module provides remote monitoring of a running process over -- HTTP. It can be used to run an HTTP server that provides both a -- web-based user interface and a machine-readable API (e.g. JSON.) -- The former can be used by a human to get an overview of what the -- program is doing and the latter can be used by automated monitoring -- tools. -- -- Typical usage is to start the monitoring server at program startup -- -- > main = do -- > forkServer "localhost" 8000 -- > ... -- -- and then periodically check the stats using a web browser or a -- command line tool (e.g. curl) -- -- > $ curl -H "Accept: application/json" http://localhost:8000/ module System.Remote.Monitoring ( -- * Required configuration -- $configuration -- * Security considerations -- $security -- * REST API -- $api -- * The monitoring server Server , serverThreadId , forkServer -- * User-defined counters, gauges, and labels -- $userdefined , getCounter , getGauge , getLabel ) where import Control.Concurrent (ThreadId, forkIO) import qualified Data.ByteString as S import qualified Data.HashMap.Strict as M import Data.IORef (newIORef) import Prelude hiding (read) import System.Remote.Common import System.Remote.Snap -- $configuration -- -- To use this module you must first enable GC statistics collection -- in the run-time system. To enable GC statistics collection, either -- run your program with -- -- > +RTS -T -- -- or compile it with -- -- > -with-rtsopts=-T -- -- The runtime overhead of @-T@ is very small so it's safe to always -- leave it enabled. -- $security -- Be aware that if the server started by 'forkServer' is not bound to -- \"localhost\" (or equivalent) anyone on the network can access the -- monitoring server. Either make sure the network is secure or bind -- the server to \"localhost\". -- $api -- To use the machine-readable REST API, send an HTTP GET request to -- the host and port passed to 'forkServer'. The following resources -- (i.e. URLs) are available: -- -- [\/] JSON object containing all counters, gauges and labels. -- Counters, gauges, and labels are stored as nested objects under the -- @counters@, @gauges@, and @labels@ attributes, respectively. -- Content types: \"text\/html\" (default), \"application\/json\" -- -- [\/combined] Flattened JSON object containing all counters, gauges, -- and labels. Content types: \"application\/json\" -- -- [\/counters] JSON object containing all counters. Content types: -- \"application\/json\" -- -- [\/counters/\] Value of a single counter, as a -- string. The name should be UTF-8 encoded. Content types: -- \"text\/plain\" -- -- [\/gauges] JSON object containing all gauges. Content types: -- \"application\/json\" -- -- [\/gauges/\] Value of a single gauge, as a string. -- The name should be UTF-8 encoded. Content types: \"text\/plain\" -- -- [\/labels] JSON object containing all labels. Content types: -- \"application\/json\" -- -- [\/labels/\