tracing-control-0.0.6: Distributed tracing

Safe HaskellNone
LanguageHaskell2010

Monitor.Tracing.Zipkin

Contents

Description

This module implements a Zipkin-powered trace publisher. You will almost certainly want to import it qualified.

Zipkin does not support all OpenTracing functionality. To guarantee that everything works as expected, you should only use the functions defined in this module or exported by Monitor.Tracing.

Synopsis

Configuration

General settings

data Settings Source #

Zipkin creation settings.

Constructors

Settings 

Fields

Instances
IsString Settings Source #

Generates settings with the given string as hostname.

Instance details

Defined in Monitor.Tracing.Zipkin

defaultSettings :: Settings Source #

Creates empty Settings. You will typically use this (or the IsString instance) as starting point to only fill in the fields you care about:

let settings = defaultSettings { settingsPort = Just 2222 }

Endpoint

data Endpoint Source #

Information about a hosted service, included in spans and visible in the Zipkin UI.

Constructors

Endpoint 

Fields

Instances
Eq Endpoint Source # 
Instance details

Defined in Monitor.Tracing.Zipkin

Ord Endpoint Source # 
Instance details

Defined in Monitor.Tracing.Zipkin

Show Endpoint Source # 
Instance details

Defined in Monitor.Tracing.Zipkin

IsString Endpoint Source #

Generates an endpoint with the given string as service.

Instance details

Defined in Monitor.Tracing.Zipkin

ToJSON Endpoint Source # 
Instance details

Defined in Monitor.Tracing.Zipkin

defaultEndpoint :: Endpoint Source #

An empty endpoint.

Publishing traces

data Zipkin Source #

A Zipkin trace publisher.

All publisher functionality is thread-safe. In particular it is safe to publish concurrently with run, and/or run multiple actions concurrently. Note also that all sampled spans are retained in memory until they are published.

new :: MonadIO m => Settings -> m Zipkin Source #

Creates a Zipkin publisher for the input Settings.

run :: TraceT m a -> Zipkin -> m a Source #

Runs a TraceT action, sampling spans appropriately. Note that this method does not publish spans on its own; to do so, either call publish manually or specify a positive settingsPublishPeriod to publish in the background.

publish :: MonadIO m => Zipkin -> m () Source #

Flushes all complete spans to the Zipkin server.

with :: (MonadIO m, MonadBaseControl IO m) => Settings -> (Zipkin -> m a) -> m a Source #

Convenience method to start a Zipkin, run an action, and publish all spans before returning.

Cross-process spans

Communication

data B3 Source #

Exportable trace information, used for cross-process traces.

Constructors

B3 

Fields

Instances
Eq B3 Source # 
Instance details

Defined in Monitor.Tracing.Zipkin

Methods

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

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

Ord B3 Source # 
Instance details

Defined in Monitor.Tracing.Zipkin

Methods

compare :: B3 -> B3 -> Ordering #

(<) :: B3 -> B3 -> Bool #

(<=) :: B3 -> B3 -> Bool #

(>) :: B3 -> B3 -> Bool #

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

max :: B3 -> B3 -> B3 #

min :: B3 -> B3 -> B3 #

Show B3 Source # 
Instance details

Defined in Monitor.Tracing.Zipkin

Methods

showsPrec :: Int -> B3 -> ShowS #

show :: B3 -> String #

showList :: [B3] -> ShowS #

b3ToHeaders :: B3 -> Map (CI ByteString) ByteString Source #

Serializes the B3 to multiple headers, suitable for HTTP requests. All byte-strings are UTF-8 encoded.

b3FromHeaders :: Map (CI ByteString) ByteString -> Maybe B3 Source #

Deserializes the B3 from multiple headers.

b3ToHeaderValue :: B3 -> ByteString Source #

Serializes the B3 to a single UTF-8 encoded header value. It will typically be set as b3 header.

b3FromHeaderValue :: ByteString -> Maybe B3 Source #

Deserializes a single header value into a B3.

Span generation

clientSpan :: MonadTrace m => Name -> (Maybe B3 -> m a) -> m a Source #

Generates a child span with CLIENT kind. This function also provides the corresponding B3 (or Nothing if tracing is inactive) so that it can be forwarded to the server. For example, to emit an HTTP request and forward the trace information in the headers:

import Network.HTTP.Simple

clientSpan "api-call" $ \(Just b3) -> $ do
  res <- httpBS "http://host/api" & addRequestHeader "b3" (b3ToHeaderValue b3)
  process res -- Do something with the response.

clientSpanWith :: MonadTrace m => (Builder -> Builder) -> Name -> (Maybe B3 -> m a) -> m a Source #

Generates a client span, optionally modifying the span's builder. This can be useful in combination with addEndpoint if the remote server does not have tracing enabled.

serverSpan :: MonadTrace m => B3 -> m a -> m a Source #

Generates a child span with SERVER kind. The client's B3 should be provided as input, for example parsed using b3FromHeaders.

serverSpanWith :: MonadTrace m => (Builder -> Builder) -> B3 -> m a -> m a Source #

Generates a server span, optionally modifying the span's builder. This can be useful in combination with addEndpoint if the remote client does not have tracing enabled.

producerSpanWith :: MonadTrace m => (Builder -> Builder) -> Name -> (Maybe B3 -> m a) -> m a Source #

Generates a child span with PRODUCER kind. This function also provides the corresponding B3 so that it can be forwarded to the consumer.

consumerSpanWith :: MonadTrace m => (Builder -> Builder) -> B3 -> m a -> m a Source #

Generates a child span with CONSUMER kind. The producer's B3 should be provided as input.

Custom metadata

Tags

tag :: MonadTrace m => Text -> Text -> m () Source #

Adds a tag to the active span.

addTag :: Text -> Text -> Builder -> Builder Source #

Adds a tag to a builder. This is a convenience method to use with childSpanWith, for example:

childSpanWith (addTag "key" "value") "run" $ action

Note that there is not difference with adding the tag after the span. So the above code is equivalent to:

childSpan "run" $ tag "key" "value" >> action

addInheritedTag :: Text -> Text -> Builder -> Builder Source #

Adds an inherited tag to a builder. Unlike a tag added via addTag, this tag:

  • will be inherited by all the span's local children.
  • can only be added at span construction time.

For example, to add an ID tag to all spans inside a trace:

rootSpanWith (addInheritedTag "id" "abcd-efg") alwaysSampled "run" $ action

Annotations

Annotations are similar to tags, but timestamped.

annotate :: MonadTrace m => Text -> m () Source #

Annotates the active span using the current time.

annotateAt :: MonadTrace m => POSIXTime -> Text -> m () Source #

Annotates the active span at the given time.

Endpoints

addEndpoint :: Endpoint -> Builder -> Builder Source #

Adds a remote endpoint to a builder. This is mostly useful when generating cross-process spans where the remote endpoint is not already traced (otherwise Zipkin will associate the spans correctly automatically). For example when emitting a request to an outside server:

clientSpanWith (addEndpoint "outside-api") -- ...