riemann-0.1.1.0: A Riemann client for Haskell

Safe HaskellNone
LanguageHaskell2010

Network.Monitoring.Riemann.Types

Synopsis

Documentation

class HasState a where Source #

HasState types (e.g. Event and State) have information representing the state of a service on a host at a given time. These shared types give rise to restrictedly polymorphic lenses.

Minimal complete definition

time, state, service, host, description, tags, ttl

Methods

time :: Lens' a (Maybe Int64) Source #

The time of the event, in unix epoch seconds

state :: Lens' a (Maybe Text) Source #

Any string less than 255 bytes, e.g. "ok", "warning", "critical"

service :: Lens' a (Maybe Text) Source #

e.g. "API port 8000 reqs/sec"

host :: Lens' a (Maybe Text) Source #

A hostname, e.g. "api1", "foo.com"

description :: Lens' a (Maybe Text) Source #

Freeform text

tags :: Lens' a [Text] Source #

Freeform list of strings, e.g. ["rate", "fooproduct", "transient"]

ttl :: Lens' a (Maybe Float) Source #

A floating-point time, in seconds, that this event is considered valid for. Expired states may be removed from the index.

class AMetric a where Source #

The class of types which can be interpreted as metrics for an Event.

Minimal complete definition

metric

Methods

metric :: Lens' Event (Maybe a) Source #

class HasQuery a where Source #

HasQuery types contain a Riemann query inside them somewhere. This class provides query as a polymorphic lens toward that query.

Minimal complete definition

query

Methods

query :: Lens' a (Maybe Text) Source #

data State Source #

State is an object within Riemann's index, a result from a Query.

Instances

Eq State Source # 

Methods

(==) :: State -> State -> Bool #

(/=) :: State -> State -> Bool #

Show State Source # 

Methods

showsPrec :: Int -> State -> ShowS #

show :: State -> String #

showList :: [State] -> ShowS #

Generic State Source # 

Associated Types

type Rep State :: * -> * #

Methods

from :: State -> Rep State x #

to :: Rep State x -> State #

Monoid State Source # 

Methods

mempty :: State #

mappend :: State -> State -> State #

mconcat :: [State] -> State #

Default State Source # 

Methods

def :: State #

Decode State Source # 
Encode State Source # 

Methods

encode :: State -> Put #

HasState State Source # 
type Rep State Source # 

data Event Source #

Event is a description of an application-level event, emitted to Riemann for indexing.

data Query Source #

Query is a question to be made of the Riemann index.

Instances

Eq Query Source # 

Methods

(==) :: Query -> Query -> Bool #

(/=) :: Query -> Query -> Bool #

Show Query Source # 

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

Generic Query Source # 

Associated Types

type Rep Query :: * -> * #

Methods

from :: Query -> Rep Query x #

to :: Rep Query x -> Query #

Monoid Query Source # 

Methods

mempty :: Query #

mappend :: Query -> Query -> Query #

mconcat :: [Query] -> Query #

Default Query Source # 

Methods

def :: Query #

Decode Query Source # 
Encode Query Source # 

Methods

encode :: Query -> Put #

HasQuery Query Source # 
type Rep Query Source # 
type Rep Query = D1 (MetaData "Query" "Network.Monitoring.Riemann.Types" "riemann-0.1.1.0-5IumlgKQOM2Ag6PMFsflaK" False) (C1 (MetaCons "Query" PrefixI True) (S1 (MetaSel (Just Symbol "_queryQuery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Optional 1 (Value Text)))))

data Msg Source #

Msg is a wrapper for sending/receiving multiple States, Events, or a single Query.

Instances

Eq Msg Source # 

Methods

(==) :: Msg -> Msg -> Bool #

(/=) :: Msg -> Msg -> Bool #

Show Msg Source # 

Methods

showsPrec :: Int -> Msg -> ShowS #

show :: Msg -> String #

showList :: [Msg] -> ShowS #

Generic Msg Source # 

Associated Types

type Rep Msg :: * -> * #

Methods

from :: Msg -> Rep Msg x #

to :: Rep Msg x -> Msg #

Monoid Msg Source # 

Methods

mempty :: Msg #

mappend :: Msg -> Msg -> Msg #

mconcat :: [Msg] -> Msg #

Default Msg Source # 

Methods

def :: Msg #

Decode Msg Source # 
Encode Msg Source # 

Methods

encode :: Msg -> Put #

HasQuery Msg Source # 
type Rep Msg Source # 

ev :: AMetric a => String -> a -> Event Source #

Create a simple Event with state "ok".

>>> view state $ ev "service" (0 :: (Signed Int64))
Just "ok"
>>> view service $ ev "service" (0 :: (Signed Int64))
Just "service"
>>> view metric $ ev "service" (0 :: (Signed Int64)) :: Maybe (Signed Int64)
Just (Signed 0)
>>> view tags $ ev "service" (0 :: (Signed Int64))
[]

data MsgState Source #

Constructors

Ok 
Error Text 
Unknown 

type Port = Int Source #