{-# LANGUAGE ExistentialQuantification, OverloadedStrings, RecordWildCards, FunctionalDependencies #-} -- | 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 -- * REST API -- $api -- * The monitoring server Server , serverThreadId , forkServer -- * User-defined counters, gauges, and labels -- $userdefined , getCounter , getGauge , getLabel ) where import Control.Applicative ((<$>), (<|>)) import Control.Concurrent (ThreadId, forkIO) import Control.Monad (forM, join, unless) import Control.Monad.IO.Class (liftIO) import qualified Data.Aeson.Encode as A import Data.Aeson.Types ((.=)) import qualified Data.Aeson.Types as A import qualified Data.ByteString as S import qualified Data.ByteString.Char8 as S8 import Data.Function (on) import qualified Data.HashMap.Strict as M import Data.IORef (IORef, atomicModifyIORef, newIORef, readIORef) import qualified Data.List as List import qualified Data.Map as Map import Data.Maybe (listToMaybe) import qualified Data.Text as T import qualified Data.Text.Encoding as T import Data.Time.Clock.POSIX (getPOSIXTime) import Data.Word (Word8) import qualified GHC.Stats as Stats import Paths_ekg (getDataDir) import Prelude hiding (read) import Snap.Core (MonadSnap, Request, Snap, finishWith, getHeaders, getRequest, getResponse, method, Method(GET), modifyResponse, pass, route, rqParams, rqPathInfo, setContentType, setResponseStatus, writeBS, writeLBS) import Snap.Http.Server (httpServe) import qualified Snap.Http.Server.Config as Config import Snap.Util.FileServe (serveDirectory) import System.FilePath (()) import System.Remote.Counter (Counter) import qualified System.Remote.Counter.Internal as Counter import System.Remote.Gauge (Gauge) import qualified System.Remote.Gauge.Internal as Gauge import System.Remote.Label (Label) import qualified System.Remote.Label.Internal as Label -- $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. -- $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 and gauges. Counters and -- gauges are stored as nested objects under the @counters@ and -- @gauges@ 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/\