core-telemetry-0.1.7.1: Advanced telemetry
Safe HaskellNone
LanguageHaskell2010

Core.Telemetry.Observability

Description

Traditional "monitoring" systems were concerned with gathering together obscene quantities of metrics and graphing them. This makes for very pretty billboard displays in Network Operations Centers which impress visitors tremendously, but (it turns out) are of limited use when actually trying to troubleshoot problems or improve the performance of our systems. We all put a lot of effort into trying to detect anamolies but really, despite person-centuries of effort, graphing raw system metrics doesn't get us as far as we would have liked.

Experience with large-scale distributed systems has led to the insight that what you need is to be able to trace the path a request takes as it moves through a system, correlating and comparing this trace to others like it. This has led to the modern "observability" movement, more concerned with metrics which descirbe user-visible experience, service levels, error budgets, and being able to do ad-hoc analysis of evolving situations.

This library aims to support both models of using telemetry, with the primary emphasis being on the traces and spans that can be connected together by an observability tool.

Usage

To use this capability, first you need to initialize the telemetry subsystem with an appropriate exporter:

import Core.Program
import Core.Telemetry

main :: IO ()
main = do
    context <- configure "1.0" None (simpleConfig [])
    context' <- initializeTelemetry [consoleExporter, structuredExporter, honeycombExporter] context
    executeWith context' program

Then when you run your program you can pick the exporter:

$ burgerservice --telemetry=structured

to activate sending telemetry, in this case, to the console in the form of structured JSON logs. Other exporters add additional command-line options with which to configure how and where the metrics will be sent.

Traces and Spans

At the top of your program or request loop you need to start a new trace (with beginTrace) or continue one inherited from another service (with usingTrace):

program :: Program None ()
program = do
    beginTrace $ do
        encloseSpan "Service request" $ do

            -- do stuff!

            ...

            obs <- currentSkyObservation
            temp <- currentAirTemperature

            ...

            -- add appropriate telemetry values to the span
            telemetry
                [ metric "sky_colour" (colourFrom obs)
                , metric "temperature" temp
                ]

will result in sky_colour="Blue" and temperature=26.1 or whatever being sent by the telemetry system to the observability service that's been activated.

The real magic here is that spans nest. As you go into each subcomponent on your request path you can again call encloseSpan creating a new span, which can have its own telemetry:

currentSkyObservation :: Program None Observation
currentSkyObservation = do
    encloseSpan "Observe sky" $ do
        ...

        telemetry
            [ metric "radar_frequency" freq
            , metric "cloud_cover" blockageLevel
            ]

        pure result

Any metrics added before entering the new span will be inherited by the subspan and sent when it finishes so you don't have to keep re-attaching data if it's common across all the spans in your trace.

Events

In other circumstances you will just want to send metrics:

        -- not again!
        sendEvent "Cat meowed"
            [ metric "room" ("living room" :: Rope)
            , metric "volume" (127.44 :: Float) -- decibels
            , metric "apparently_hungry" True
            ]

will result in room="living room", volume=127.44, and apparently_hungry=true being sent as you'd expect. Ordinarily when you call metric you are passing in a variable that already has a type, but when hardcoding literals like in this example (less common but not unheard of) you'll need to add a type annotation.

You do not have to call sendEvent from within a span, but if you do appropriate metadata will be added to help the observability system link the event to the context of the span it occured during.

Either way, explicitly sending an event, or upon exiting a span, the telemetry will be gathered up and sent via the chosen exporter and forwarded to the observability or monitoring service you have chosen.

Synopsis

Initializing

data Exporter #

initializeTelemetry :: [Exporter] -> Context τ -> IO (Context τ) Source #

Activate the telemetry subsystem for use within the Program monad.

Each exporter specified here will add setup and configuration to the context, including command-line options and environment variables needed as approrpiate:

    context' <- initializeTelemetry [consoleExporter] context

This will allow you to then select the appropriate backend at runtime:

$ burgerservice --telemetry=console

which will result in it spitting out metrics as it goes,

  calories = 667.0
  flavour = true
  meal_name = "hamburger"
  precise = 45.0

and so on.

Traces

newtype Trace #

Unique identifier for a trace. If your program is the top of an service stack then you can use beginTrace to generate a new idenfifier for this request or iteration. More commonly, however, you will inherit the trace identifier from the application or service which invokes this program or request handler, and you can specify it by using usingTrace.

Constructors

Trace Rope 

Instances

Instances details
Show Trace 
Instance details

Defined in Core.Program.Context

Methods

showsPrec :: Int -> Trace -> ShowS #

show :: Trace -> String #

showList :: [Trace] -> ShowS #

IsString Trace 
Instance details

Defined in Core.Program.Context

Methods

fromString :: String -> Trace #

newtype Span #

Unique identifier for a span. This will be generated by encloseSpan but for the case where you are continuing an inherited trace and passed the identifier of the parent span you can specify it using this constructor.

Constructors

Span Rope 

Instances

Instances details
Show Span 
Instance details

Defined in Core.Program.Context

Methods

showsPrec :: Int -> Span -> ShowS #

show :: Span -> String #

showList :: [Span] -> ShowS #

IsString Span 
Instance details

Defined in Core.Program.Context

Methods

fromString :: String -> Span #

beginTrace :: Program τ α -> Program τ α Source #

Start a new trace. A random identifier will be generated.

You must have a single "root span" immediately below starting a new trace.

program :: Program None ()
program = do
    beginTrace $ do
        encloseSpan "Service Request" $ do
            ...

usingTrace :: Trace -> Maybe Span -> Program τ α -> Program τ α Source #

Begin a new trace, but using a trace identifier provided externally. This is the most common case. Internal services that are play a part of a larger request will inherit a job identifier, sequence number, or other externally supplied unique code. Even an internet facing web service might have a correlation ID provided by the outside load balancers.

If you are continuting an existing trace within the execution path of another, larger, enclosing service then you need to specify what the parent span's identifier is in the second argument.

program :: Program None ()
program = do

    -- do something that gets the trace ID
    trace <- ...

    -- and something to get the parent span ID
    parent <- ...

    usingTrace (Trace trace) (Just (Span span)) $ do
        encloseSpan "Internal processing" $ do
            ...

setServiceName :: Rope -> Program τ () Source #

Record the name of the service that this span and its children are a part of. A reasonable default is the name of the binary that's running, but frequently you'll want to put something a bit more nuanced or specific to your application. This is the overall name of the independent service, component, or program complimenting the label set when calling encloseSpan, which by contrast descibes the name of the current phase, step, or even function name within the overall scope of the "service".

This will end up as the service_name parameter when exported.

Spans

encloseSpan :: Label -> Program z a -> Program z a Source #

Begin a span.

You need to call this from within the context of a trace, which is established either by calling beginTrace or usingTrace somewhere above this point in the program.

You can nest spans as you make your way through your program, which means each span has a parent (except for the first one, which is the root span) In the context of a trace, allows an observability tool to reconstruct the sequence of events and to display them as a nested tree correspoding to your program flow.

The current time will be noted when entering the Program this span encloses, and its duration recorded when the sub Program exits. Start time, duration, the unique identifier of the span (generated for you), the identifier of the parent, and the unique identifier of the overall trace will be appended as metadata points and then sent to the telemetry channel.

setStartTime :: TimeStamp -> Program τ () Source #

Override the start time of the current span.

Under normal circumstances this shouldn't be necessary. The start and end of a span are recorded automatically when calling encloseSpan. Observabilty tools are designed to be used live; traces and spans should be created in real time in your code.

Creating telemetry

data MetricValue Source #

A telemetry value that can be sent over the wire. This is a wrapper around JSON values of type string, number, or boolean. You create these using the metric method provided by a Telemetry instance and passing them to the telemetry function in a span or sendEvent if noting an event.

Instances

Instances details
Show MetricValue Source # 
Instance details

Defined in Core.Telemetry.Observability

class Telemetry σ where Source #

Methods

metric :: Rope -> σ -> MetricValue Source #

Instances

Instances details
Telemetry Bool Source # 
Instance details

Defined in Core.Telemetry.Observability

Telemetry Double Source # 
Instance details

Defined in Core.Telemetry.Observability

Telemetry Float Source # 
Instance details

Defined in Core.Telemetry.Observability

Telemetry Int Source # 
Instance details

Defined in Core.Telemetry.Observability

Methods

metric :: Rope -> Int -> MetricValue Source #

Telemetry Int32 Source # 
Instance details

Defined in Core.Telemetry.Observability

Telemetry Int64 Source # 
Instance details

Defined in Core.Telemetry.Observability

Telemetry Integer Source # 
Instance details

Defined in Core.Telemetry.Observability

Telemetry ByteString Source #

The usual warning about assuming the ByteString is ASCII or UTF-8 applies here. Don't use this to send binary mush.

Instance details

Defined in Core.Telemetry.Observability

Telemetry ByteString Source #

The usual warning about assuming the ByteString is ASCII or UTF-8 applies here. Don't use this to send binary mush.

Instance details

Defined in Core.Telemetry.Observability

Telemetry Scientific Source # 
Instance details

Defined in Core.Telemetry.Observability

Telemetry String Source # 
Instance details

Defined in Core.Telemetry.Observability

Telemetry Text Source # 
Instance details

Defined in Core.Telemetry.Observability

Telemetry Text Source # 
Instance details

Defined in Core.Telemetry.Observability

Telemetry Rope Source # 
Instance details

Defined in Core.Telemetry.Observability

Telemetry JsonValue Source # 
Instance details

Defined in Core.Telemetry.Observability

telemetry :: [MetricValue] -> Program τ () Source #

Add measurements to the current span.

        telemetry
            [ metric "calories" (667 :: Int)
            , metric "precise" measurement
            , metric "meal_name" ("hamburger" :: Rope)
            , metric "flavour" True
            ]

The metric function is a method provided by instances of the Telemtetry typeclass which is mostly a wrapper around constructing key/value pairs suitable to be sent as measurements up to an observability service.

Events

sendEvent :: Label -> [MetricValue] -> Program τ () Source #

Record telemetry about an event. Specify a label for the event and then whichever metrics you wish to record.

The emphasis of this package is to create traces and spans. There are, however, times when you just want to send telemetry about an event. You can use sendEvent to accomplish this.

If you do call sendEvent within an enclosing span created with encloseSpan (the usual and expected use case) then this event will be "linked" to this span so that the observability tool can display it attached to the span in the in which it occured.

        sendEvent
            "Make tea"
            [ metric "sugar" False
            ]