-
-
Notifications
You must be signed in to change notification settings - Fork 37
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
base: main
Are you sure you want to change the base?
Changes from all commits
File filter
Filter by extension
Conversations
Jump to
Diff view
Diff view
There are no files selected for viewing
Original file line number | Diff line number | Diff line change |
---|---|---|
|
@@ -2,6 +2,7 @@ | |
{-# LANGUAGE LambdaCase #-} | ||
{-# LANGUAGE NumericUnderscores #-} | ||
{-# LANGUAGE ScopedTypeVariables #-} | ||
{-# LANGUAGE TemplateHaskell #-} | ||
{-# LANGUAGE TypeApplications #-} | ||
{-# LANGUAGE TypeFamilies #-} | ||
|
||
|
@@ -65,6 +66,8 @@ module OpenTelemetry.Trace.Core ( | |
InstrumentationLibrary (..), | ||
TracerOptions (..), | ||
tracerOptions, | ||
ExceptionEnricher(..), | ||
discoverExceptionEnrichers, | ||
|
||
-- * Span operations | ||
Span, | ||
|
@@ -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 | ||
|
@@ -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 -> [] | ||
|
||
inSpan'' :: | ||
(MonadUnliftIO m, HasCallStack) => | ||
|
@@ -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
There was a problem hiding this comment. Choose a reason for hiding this commentThe reason will be displayed to describe this comment to others. Learn more. I feel like what I usually see is a configurable function, like For this pattern, we can do: data TracerProvider = TracerProvider
{ ...
, tracerProviderExceptionToAttributes :: SomeException -> [(Text, Attr)]
} Which removes the need for the 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 instance HasExceptionEnricher SomeAsyncException where
exceptionEnricher _ = ExceptionEnricher
do \(SomeAsyncException e) ->
-- well, we can't really do anything interesting here
do "SomeAsyncException"
There was a problem hiding this comment. Choose a reason for hiding this commentThe 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. |
||
|
@@ -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
There was a problem hiding this comment. Choose a reason for hiding this commentThe reason will be displayed to describe this comment to others. Learn more. Hmm. Thinking about how I'd write this for 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)
}
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.
There was a problem hiding this comment. Choose a reason for hiding this commentThe reason will be displayed to describe this comment to others. Learn more. Yeah, so that's why I took the approach of providing There are two things I'm trying to solve here:
There was a problem hiding this comment. Choose a reason for hiding this commentThe reason will be displayed to describe this comment to others. Learn more. Yeah, I think we do need the function parameter to have a 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 Figuring out the exact right implementation for this is subtle, though. 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 |
||
|
||
-- 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 | ||
|
@@ -674,6 +702,7 @@ data TracerProviderOptions = TracerProviderOptions | |
, tracerProviderOptionsSpanLimits :: SpanLimits | ||
, tracerProviderOptionsPropagators :: Propagator Context RequestHeaders ResponseHeaders | ||
, tracerProviderOptionsLogger :: Log Text -> IO () | ||
, tracerProviderOptionsExceptionEnrichers :: [ExceptionEnricher] | ||
} | ||
|
||
|
||
|
@@ -693,6 +722,7 @@ emptyTracerProviderOptions = | |
defaultSpanLimits | ||
mempty | ||
(\_ -> pure ()) | ||
[] | ||
|
||
|
||
{- | Initialize a new tracer provider | ||
|
@@ -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 | ||
|
There was a problem hiding this comment.
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: