statsd-0.1.0.1: StatsD API.

Safe HaskellNone
LanguageHaskell2010

Statsd

Contents

Synopsis

Types

data StatsdT m a Source

The StatsdT monad transformer. Pushing to StatsD occurs in this monad, and the computation is run with runStatsd.

type Statsd a = StatsdT IO a Source

A simple type alias for pushing to StatsD in IO.

type Bucket = ByteString Source

A StatsD bucket.

type SamplePct = Double Source

Counter sample percent. Must be between 0.0 and 1.0, inclusive.

StatsD API

runStatsd :: (MonadBaseControl IO m, MonadIO m) => Family -> SocketType -> ProtocolNumber -> SockAddr -> StatsdT m a -> m a Source

Run a StatsdT computation, which pushes metrics to StatsD.

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards   #-}

module Main where

import Network
import Network.Socket
import Statsd

main :: IO ()
main = do
    let hints   = defaultHints
                    { addrFamily     = AF_INET
                    , addrSocketType = Datagram
                    }
        host    = "localhost"
        service = "8125"

    AddrInfo{..}:_ <- getAddrInfo (Just hints) (Just host) (Just service)
    runStatsd addrFamily addrSocketType addrProtocol addrAddress $ do
        statsdCounter "foo" 1
        statsdTimer "bar" 25

statsdCounter :: MonadIO m => Bucket -> Int -> StatsdT m () Source

Push to a StatsD counter.

statsdCounter "foo" 1 == "foo:1|c"

statsdSampledCounter :: MonadIO m => Bucket -> Int -> SamplePct -> StatsdT m () Source

Push to a StatsD counter, sampled.

statsdSampledCounter "foo" 1 0.5 == "foo:1|c|@0.5"

statsdTimer :: MonadIO m => Bucket -> Int -> StatsdT m () Source

Push to a StatsD timer.

statsdTimer "foo" 1 == "foo:1|ms"

statsdGauge :: MonadIO m => Bucket -> Int -> StatsdT m () Source

Push to a StatsD gauge.

statsdGauge "foo" 1 == "foo:1|g"

statsdGaugePlus :: MonadIO m => Bucket -> Int -> StatsdT m () Source

Push a positive delta to a StatsD gauge.

statsdGaugePlus "foo" 1 == "foo:+1|g"

statsdGaugeMinus :: MonadIO m => Bucket -> Int -> StatsdT m () Source

Push a negative delta to a StatsD gauge.

statsdGaugePlus "foo" 1 == "foo:-1|g"

statsdSet :: MonadIO m => Bucket -> Int -> StatsdT m () Source

Push to a StatsD set.

statsdGaugePlus "foo" 1 == "foo:1|s"