hs-opentelemetry-api-0.2.0.0: OpenTelemetry API for use by libraries for direct instrumentation or wrapper packages.
Safe HaskellSafe-Inferred
LanguageHaskell2010

OpenTelemetry.Internal.Common.Types

Synopsis

Documentation

data InstrumentationLibrary Source #

An identifier for the library that provides the instrumentation for a given Instrumented Library. Instrumented Library and Instrumentation Library may be the same library if it has built-in OpenTelemetry instrumentation.

The inspiration of the OpenTelemetry project is to make every library and application observable out of the box by having them call OpenTelemetry API directly. However, many libraries will not have such integration, and as such there is a need for a separate library which would inject such calls, using mechanisms such as wrapping interfaces, subscribing to library-specific callbacks, or translating existing telemetry into the OpenTelemetry model.

A library that enables OpenTelemetry observability for another library is called an Instrumentation Library.

An instrumentation library should be named to follow any naming conventions of the instrumented library (e.g. middleware for a web framework).

If there is no established name, the recommendation is to prefix packages with "hs-opentelemetry-instrumentation", followed by the instrumented library name itself.

In general, the simplest way to get the instrumentation library is to use detectInstrumentationLibrary, which uses the Haskell package name and version.

Constructors

InstrumentationLibrary 

Fields

Instances

Instances details
IsString InstrumentationLibrary Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

Generic InstrumentationLibrary Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

Associated Types

type Rep InstrumentationLibrary :: Type -> Type #

Show InstrumentationLibrary Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

Eq InstrumentationLibrary Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

Ord InstrumentationLibrary Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

Hashable InstrumentationLibrary Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

Lift InstrumentationLibrary Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

type Rep InstrumentationLibrary Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

type Rep InstrumentationLibrary = D1 ('MetaData "InstrumentationLibrary" "OpenTelemetry.Internal.Common.Types" "hs-opentelemetry-api-0.2.0.0-2Szn2AZ2vnoHm5uYEjNBGv" 'False) (C1 ('MetaCons "InstrumentationLibrary" 'PrefixI 'True) ((S1 ('MetaSel ('Just "libraryName") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "libraryVersion") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "librarySchemaUrl") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "libraryAttributes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Attributes))))

data AnyValue Source #

An attribute represents user-provided metadata about a span, link, or event.

Any values are used in place of 'Standard Attributes' in logs because third-party logs may not conform to the 'Standard Attribute' format.

Telemetry tools may use this data to support high-cardinality querying, visualization in waterfall diagrams, trace sampling decisions, and more.

Instances

Instances details
Data AnyValue Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnyValue -> c AnyValue #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnyValue #

toConstr :: AnyValue -> Constr #

dataTypeOf :: AnyValue -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnyValue) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnyValue) #

gmapT :: (forall b. Data b => b -> b) -> AnyValue -> AnyValue #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnyValue -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnyValue -> r #

gmapQ :: (forall d. Data d => d -> u) -> AnyValue -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AnyValue -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnyValue -> m AnyValue #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnyValue -> m AnyValue #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnyValue -> m AnyValue #

IsString AnyValue Source #

Create a TextAttribute from the string value.

Instance details

Defined in OpenTelemetry.Internal.Common.Types

Generic AnyValue Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

Associated Types

type Rep AnyValue :: Type -> Type #

Methods

from :: AnyValue -> Rep AnyValue x #

to :: Rep AnyValue x -> AnyValue #

Read AnyValue Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

Show AnyValue Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

Eq AnyValue Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

Ord AnyValue Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

Hashable AnyValue Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

Methods

hashWithSalt :: Int -> AnyValue -> Int #

hash :: AnyValue -> Int #

ToValue AnyValue Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

type Rep AnyValue Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

class ToValue a where Source #

Convert a Haskell value to an Any value.

data Foo = Foo

instance ToValue Foo where
  toValue Foo = TextValue Foo

Methods

toValue :: a -> AnyValue Source #

Instances

Instances details
ToValue Int64 Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

ToValue ByteString Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

ToValue AnyValue Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

ToValue Text Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

ToValue Bool Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

ToValue Double Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

ToValue a => ToValue [a] Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

Methods

toValue :: [a] -> AnyValue Source #

ToValue a => ToValue (HashMap Text a) Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

data FlushResult Source #

The outcome of a call to OpenTelemetry.Trace.forceFlush or OpenTelemetry.Logs.forceFlush

Constructors

FlushTimeout

One or more spans or LogRecords did not export from all associated exporters within the alotted timeframe.

FlushSuccess

Flushing spans or LogRecords to all associated exporters succeeded.

FlushError

One or more exporters failed to successfully export one or more unexported spans or LogRecords.

Instances

Instances details
Show FlushResult Source # 
Instance details

Defined in OpenTelemetry.Internal.Common.Types

parseInstrumentationLibrary :: MonadFail m => String -> m InstrumentationLibrary Source #

Parses a package-version string into an InstrumentationLibrary'.

detectInstrumentationLibrary :: forall m. (Quasi m, Quote m) => m Exp Source #

Works out the instrumentation library for your package.