Skip to content
New issue

Have a question about this project? Sign up for a free GitHub account to open an issue and contact its maintainers and the community.

By clicking “Sign up for GitHub”, you agree to our terms of service and privacy statement. We’ll occasionally send you account related emails.

Already on GitHub? Sign in to your account

Add interface for libraries to register exception enrichment #47

Draft
wants to merge 1 commit into
base: main
Choose a base branch
from
Draft
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 4 additions & 0 deletions api/hs-opentelemetry-api.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -75,13 +75,15 @@ library
, charset
, clock
, containers
, discover-instances
, ghc-prim
, hashable
, http-types
, memory
, mtl
, template-haskell
, text
, th-compat
, thread-utils-context ==0.2.*
, unliftio-core
, unordered-containers
Expand Down Expand Up @@ -112,6 +114,7 @@ test-suite hs-opentelemetry-api-test
, charset
, clock
, containers
, discover-instances
, ghc-prim
, hashable
, hs-opentelemetry-api
Expand All @@ -121,6 +124,7 @@ test-suite hs-opentelemetry-api-test
, mtl
, template-haskell
, text
, th-compat
, thread-utils-context ==0.2.*
, unliftio-core
, unordered-containers
Expand Down
3 changes: 3 additions & 0 deletions api/package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -43,6 +43,9 @@ dependencies:
- ghc-prim
- unliftio-core
- vector-builder
- discover-instances
- th-compat
- template-haskell

library:
source-dirs: src
Expand Down
10 changes: 9 additions & 1 deletion api/src/OpenTelemetry/Internal/Trace/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@
module OpenTelemetry.Internal.Trace.Types where

import Control.Concurrent.Async (Async)
import Control.Exception (SomeException)
import Control.Exception (SomeException, Exception)
import Control.Monad.IO.Class
import Data.Bits
import Data.HashMap.Strict (HashMap)
Expand Down Expand Up @@ -117,6 +117,13 @@ data Processor = Processor
-- ForceFlush SHOULD complete or abort within some timeout. ForceFlush can be implemented as a blocking API or an asynchronous API which notifies the caller via a callback or an event. OpenTelemetry client authors can decide if they want to make the flush timeout configurable.
}

-- | Similar to 'Control.Exception.Handler` but solely used for the purpose of
-- extracting additional information from exceptions to attach to the spans that
-- contain the thrown exception.
data ExceptionEnricher = forall e. Exception e => ExceptionEnricher
{ exceptionEnricherAdditionalFields :: e -> [(Text, Attribute)]
, exceptionEnricherName :: Text
}

{- |
'Tracer's can be created from a 'TracerProvider'.
Expand All @@ -130,6 +137,7 @@ data TracerProvider = TracerProvider
, tracerProviderSpanLimits :: !SpanLimits
, tracerProviderPropagators :: !(Propagator Context RequestHeaders ResponseHeaders)
, tracerProviderLogger :: Log Text -> IO ()
, tracerProviderExceptionEnrichers :: !(Vector ExceptionEnricher)
}


Expand Down
38 changes: 34 additions & 4 deletions api/src/OpenTelemetry/Trace/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}

Expand Down Expand Up @@ -65,6 +66,8 @@ module OpenTelemetry.Trace.Core (
InstrumentationLibrary (..),
TracerOptions (..),
tracerOptions,
ExceptionEnricher(..),
discoverExceptionEnrichers,

-- * Span operations
Span,
Expand Down Expand Up @@ -151,7 +154,10 @@ import qualified Data.Text as T
import Data.Typeable
import qualified Data.Vector as V
import Data.Word (Word64)
import DiscoverInstances
import GHC.Stack
import Language.Haskell.TH (Q)
import Language.Haskell.TH.Syntax.Compat (SpliceQ, bindCode)
import Network.HTTP.Types
import OpenTelemetry.Attributes
import qualified OpenTelemetry.Attributes as A
Expand Down Expand Up @@ -342,6 +348,13 @@ inSpan' ::
m a
inSpan' t = inSpan'' t callStack

catchesHandler :: ExceptionEnricher -> SomeException -> [(Text, Attribute)]
catchesHandler handler e = tryHandler handler
where
tryHandler (ExceptionEnricher handler _)
= case fromException e of
Just e' -> handler e'
Nothing -> []
Comment on lines +351 to +357
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

hrm, I found the name shadowing a bit confusing here. Would probably prefer to inline some of that:

Suggested change
catchesHandler :: ExceptionEnricher -> SomeException -> [(Text, Attribute)]
catchesHandler handler e = tryHandler handler
where
tryHandler (ExceptionEnricher handler _)
= case fromException e of
Just e' -> handler e'
Nothing -> []
catchesHandler :: ExceptionEnricher -> SomeException -> [(Text, Attribute)]
catchesHandler (ExceptionEnricher handler _) e =
case fromException e of
Just e' -> handler e'
Nothing -> []


inSpan'' ::
(MonadUnliftIO m, HasCallStack) =>
Expand Down Expand Up @@ -375,9 +388,11 @@ inSpan'' t cs n args f = do
pure (lookupSpan ctx, s)
)
( \e (parent, s) -> liftIO $ do
forM_ e $ \(SomeException inner) -> do
forM_ e $ \anException@(SomeException inner) -> do
setStatus s $ Error $ T.pack $ displayException inner
recordException s [] Nothing inner
let exceptionAttributes = concatMap (\enricher -> catchesHandler enricher anException) $
V.toList (tracerProviderExceptionEnrichers $ tracerProvider t)
recordException s exceptionAttributes Nothing inner
endSpan s Nothing
adjustContext $ \ctx ->
maybe (removeSpan ctx) (`insertSpan` ctx) parent
Comment on lines 390 to 398
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I feel like what I usually see is a configurable function, like data Settings = Settings { settingsOnException :: SomeException -> IO () }.

For this pattern, we can do:

data TracerProvider = TracerProvider 
  { ...
  , tracerProviderExceptionToAttributes :: SomeException -> [(Text, Attr)]
  }

Which removes the need for the ExceptionEnricher complexity.

But, is this equivalent?

Let's write one that pulls annotations off an annotated exception.

tracerProvider = TracerProvicer {..}
  where
    tracerProviderExceptionToAttributes somE@(SomeException inner) 
      -- because fromException always succeeds, don't want to infinite recursion
      | Just (AnnotatedException anns err) <- cast inner 
      = convertAnnotations anns <> tracerProvicerExceptionToAttributes (toException err)
      | Just (SomeAsyncException inner) <- fromException somE
      = ("Async Exception", _) : tracerProviderExceptionToAttributes (SomeException inner)
      -- use `SomeException` instead of `toException` because `toException` will rewrap in `SomeAsyncException`

Hmm, already getting pretty complex...

But I think it's probably better than the ExceptionEnricher class, which doesn't locally know what the other things are doing.

instance HasExceptionEnricher SomeAsyncException where
    exceptionEnricher _ = ExceptionEnricher 
      do \(SomeAsyncException e) -> 
           -- well, we can't really do anything interesting here
      do "SomeAsyncException"

AnnotatedException is able to summon the canonical ExceptionEnricher for a type, since it has the type parameter. But no other exception wrapper would work.

Copy link
Owner Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I suppose we could work around the wrapper issue by passing in known exception enrichers to the function:

data ExceptionEnricher = forall e. Exception e => ExceptionEnricher
  { exceptionEnricherAdditionalFields :: [ExceptionEnricher] {- ^ all known enrichers -} -> e -> [(Text, Attribute)]
  , exceptionEnricherName :: Text
  }

That would allow us in the case of wrappers to feed the inner exception through the same process.

Expand Down Expand Up @@ -665,6 +680,19 @@ globalTracer = unsafePerformIO $ do
newIORef p
{-# NOINLINE globalTracer #-}

-- | This type class allows library authors and users to enrich the
-- contents of an exception with additional attributes.
class Exception e => HasExceptionEnricher e where
exceptionEnricher :: Proxy e -> ExceptionEnricher
Comment on lines +683 to +686
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Hmm. Thinking about how I'd write this for annotated-exception.

instance (HasExceptionEnricher e) => HasExceptionEnricher (AnnotatedException e) where
  exceptionEnricher _ = ExceptionEnricher
    { exceptionEnricherAdditionalFields = \(AnnotatedException anns er) ->
        exceptionEnricherAdditionalFields (exceptionEnricher (pure er)) e
        <> makeAdditionalFields anns
    , exceptionEnricherName = "AnnotatedException " <> show (typeRep @e)
    }

makeAdditionalFields is pretty limited- it can only access the Annotation, which can only really be shown into a String. So the only real impl would be something like map (\(Annotation ann) -> (Text.pack (show $ typeRep (pure ann)), show ann)) annotations.

I would expect that apps would want to customize this directly, for their own app. So having a type class may not be the best way to do that.

discoverInstances also only works "transitively" in the same package, otherwise you do need the type itself imported in a module (and used!) or it won't discover the instance.

Copy link
Owner Author

@iand675 iand675 Dec 16, 2022

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Yeah, so that's why I took the approach of providing tracerProviderOptionsExceptionEnrichers.

There are two things I'm trying to solve here:

  1. This is the hs-opentelemetry-api package, which is intended to be usable by libraries (such as persistent) in such a fashion that they have no effect if you aren't using hs-opentelemetry-sdk in your application. I'd like to provide a mechanism for domain-specific exceptions to provide additional attributes to the span, which is why the ExceptionEnricher + type class + discoverExceptionEnricher mechanism exists. I know it's a bit brittle in that you have to import the right things in the right module, but I'm not sure how else to provide any amount of automatic hookup for library-supplied enrichers.
  2. I don't want the type class instance auto-discovery bits to be required to use the library, which is why any discovered enrichers ultimately have to be set in the tracerProviderOptionsExceptionEnrichers :: [ExceptionEnricher] record field. In the case of wanting to do more than rendering annotations to a string, this would presumably be where you'd be able to append a domain-specific ExceptionEnricher that can leverage Typeable to do more useful annotations.

Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Yeah, I think we do need the function parameter to have a [Enricher] parameter - otherwise, we can only deal with the things that are known that that point in time. I ran into this same problem when considering a plain function approach - you can recurse into wrappers just fine, and you can compose SomeException -> [(Text, Attribute)] fine with <>, but you can't make a wrapper that can see through other wrappers defined later, unless you accept the final :: [Enricher] as a late bound function argument.

Playing with it this afternoon and I got:

newtype Enricher = Enricher ([Enricher] -> SomeException -> [(Text, Attribute)])
    deriving newtype (Semigroup, Monoid)

enrich :: SomeException -> [Enricher] -> [(Text, Attribute)]
enrich exception enrichers = 
    foldMap (\(Enricher k) -> k enrichers exception)

simpleEnricher :: Exception e => (e -> [(Text, Attribute)]) -> Enricher
simpleEnricher k =
    Enricher \_ someException -> 
        foldMap k (fromException someException)

nestedEnricher :: Exception e => ([Enricher] -> e -> [(Text, Attribute)]) -> Enricher
nestedEnricher k =
    Enricher \final exception -> 
        foldMap (k final) (fromException exception) 

Each library can define an Enricher for a specific exception, then mconcat them all into a single Enricher.

Figuring out the exact right implementation for this is subtle, though. cast and fromException need to be chosen with care, or you may get into infinite loops. So I think it's important to figure out some basic tests (SomeException, SomeAsyncException, SyncExceptionWrapper, AsyncExceptionWrapper, AnnotatedException, etc) and ensure we're getting the right behavior.

Figuring out the plugin-UX side of things can happen at a later step. IMO it's fine to say "You need to import the Enricher for a given library and plug it in to the settings." Very few libraries work in any other way.


-- Find all in-scope enrichers that are provided by the @HasExceptionEnricher@ type class.
--
-- > emptyTracerProviderOptions
-- > { tracerProviderExceptionEnrichers = $$discoverExceptionEnrichers
-- > }
discoverExceptionEnrichers :: SpliceQ [ExceptionEnricher]
discoverExceptionEnrichers =
[||map (\(SomeDictOf proxy) -> exceptionEnricher proxy) $$(discoverInstances @HasExceptionEnricher)||]

data TracerProviderOptions = TracerProviderOptions
{ tracerProviderOptionsIdGenerator :: IdGenerator
Expand All @@ -674,6 +702,7 @@ data TracerProviderOptions = TracerProviderOptions
, tracerProviderOptionsSpanLimits :: SpanLimits
, tracerProviderOptionsPropagators :: Propagator Context RequestHeaders ResponseHeaders
, tracerProviderOptionsLogger :: Log Text -> IO ()
, tracerProviderOptionsExceptionEnrichers :: [ExceptionEnricher]
}


Expand All @@ -693,6 +722,7 @@ emptyTracerProviderOptions =
defaultSpanLimits
mempty
(\_ -> pure ())
[]


{- | Initialize a new tracer provider
Expand All @@ -701,17 +731,17 @@ emptyTracerProviderOptions =
-}
createTracerProvider :: MonadIO m => [Processor] -> TracerProviderOptions -> m TracerProvider
createTracerProvider ps opts = liftIO $ do
let g = tracerProviderOptionsIdGenerator opts
pure $
TracerProvider
(V.fromList ps)
g
(tracerProviderOptionsIdGenerator opts)
(tracerProviderOptionsSampler opts)
(tracerProviderOptionsResources opts)
(tracerProviderOptionsAttributeLimits opts)
(tracerProviderOptionsSpanLimits opts)
(tracerProviderOptionsPropagators opts)
(tracerProviderOptionsLogger opts)
(V.fromList $ tracerProviderOptionsExceptionEnrichers opts)


{- | Access the globally configured 'TracerProvider'. Once the
Expand Down