tracing-0.0.2.3: 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.

Synopsis

Configuration

General settings

data Settings Source #

Zipkin creation settings. Note that its constructor is not exposed to allow backwards compatible evolution; Settings should instead be created either via defaultSettings or its IsString instance.

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 }

settingsHostname :: Settings -> Maybe HostName Source #

The Zipkin server's hostname, defaults to localhost if unset.

settingsPort :: Settings -> Maybe PortNumber Source #

The port the Zipkin server is listening on, defaults to 9411 if unset.

settingsManager :: Settings -> Maybe Manager Source #

An optional HTTP manager to use for publishing spans on the Zipkin server.

settingsEndpoint :: Settings -> Maybe Endpoint Source #

Local endpoint included in all published spans.

settingsPublishPeriod :: Settings -> Maybe NominalDiffTime Source #

If set to a positive value, traces will be flushed in the background every such period.

Endpoint

data Endpoint Source #

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

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.

endpointService :: Endpoint -> Maybe Text Source #

The endpoint's service name.

endpointPort :: Endpoint -> Maybe Int Source #

The endpoint's port, if applicable and known.

endpointIPv4 :: Endpoint -> Maybe IPv4 Source #

The endpoint's IPv4 address.

endpointIPv6 :: Endpoint -> Maybe IPv6 Source #

The endpoint's IPv6 address.

Publishing traces

data Zipkin Source #

A Zipkin trace publisher.

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. This method is thread-safe.

with :: MonadUnliftIO 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.

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 => Maybe Endpoint -> 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:

clientSpan "api-call" $ \(Just b3) -> $ do
  res <- httpLbs "http://host/api" { requestHeaders = b3ToHeaders b3 }
  process res -- Do something with the response.

serverSpan :: MonadTrace m => Maybe Endpoint -> 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 b3FromRequestHeaders.

producerSpan :: MonadTrace m => Maybe Endpoint -> 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.

consumerSpan :: MonadTrace m => Maybe Endpoint -> B3 -> m a -> m a Source #

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

Custom metadata

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

Adds a tag to the active span.

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.