{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
module OpenTelemetry.Internal.Trace.Types where
import Control.Concurrent.Async (Async)
import Control.Exception (SomeException)
import Control.Monad.IO.Class
import Data.Bits
import Data.Hashable (Hashable)
import Data.HashMap.Strict (HashMap)
import Data.IORef (IORef, readIORef)
import Data.String ( IsString(..) )
import Data.Text (Text)
import Data.Vector (Vector)
import Data.Word (Word8)
import GHC.Generics
import Network.HTTP.Types (RequestHeaders, ResponseHeaders)
import OpenTelemetry.Attributes
import OpenTelemetry.Common
import OpenTelemetry.Context.Types
import OpenTelemetry.Logging.Core (Log)
import OpenTelemetry.Trace.Id
import OpenTelemetry.Resource
import OpenTelemetry.Trace.Id.Generator
import OpenTelemetry.Propagator (Propagator)
import OpenTelemetry.Trace.TraceState
import OpenTelemetry.Util
data ExportResult
= Success
| Failure (Maybe SomeException)
data InstrumentationLibrary = InstrumentationLibrary
{ InstrumentationLibrary -> Text
libraryName :: {-# UNPACK #-} !Text
, InstrumentationLibrary -> Text
libraryVersion :: {-# UNPACK #-} !Text
} deriving (Eq InstrumentationLibrary
Eq InstrumentationLibrary
-> (InstrumentationLibrary -> InstrumentationLibrary -> Ordering)
-> (InstrumentationLibrary -> InstrumentationLibrary -> Bool)
-> (InstrumentationLibrary -> InstrumentationLibrary -> Bool)
-> (InstrumentationLibrary -> InstrumentationLibrary -> Bool)
-> (InstrumentationLibrary -> InstrumentationLibrary -> Bool)
-> (InstrumentationLibrary
-> InstrumentationLibrary -> InstrumentationLibrary)
-> (InstrumentationLibrary
-> InstrumentationLibrary -> InstrumentationLibrary)
-> Ord InstrumentationLibrary
InstrumentationLibrary -> InstrumentationLibrary -> Bool
InstrumentationLibrary -> InstrumentationLibrary -> Ordering
InstrumentationLibrary
-> InstrumentationLibrary -> InstrumentationLibrary
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: InstrumentationLibrary
-> InstrumentationLibrary -> InstrumentationLibrary
$cmin :: InstrumentationLibrary
-> InstrumentationLibrary -> InstrumentationLibrary
max :: InstrumentationLibrary
-> InstrumentationLibrary -> InstrumentationLibrary
$cmax :: InstrumentationLibrary
-> InstrumentationLibrary -> InstrumentationLibrary
>= :: InstrumentationLibrary -> InstrumentationLibrary -> Bool
$c>= :: InstrumentationLibrary -> InstrumentationLibrary -> Bool
> :: InstrumentationLibrary -> InstrumentationLibrary -> Bool
$c> :: InstrumentationLibrary -> InstrumentationLibrary -> Bool
<= :: InstrumentationLibrary -> InstrumentationLibrary -> Bool
$c<= :: InstrumentationLibrary -> InstrumentationLibrary -> Bool
< :: InstrumentationLibrary -> InstrumentationLibrary -> Bool
$c< :: InstrumentationLibrary -> InstrumentationLibrary -> Bool
compare :: InstrumentationLibrary -> InstrumentationLibrary -> Ordering
$ccompare :: InstrumentationLibrary -> InstrumentationLibrary -> Ordering
$cp1Ord :: Eq InstrumentationLibrary
Ord, InstrumentationLibrary -> InstrumentationLibrary -> Bool
(InstrumentationLibrary -> InstrumentationLibrary -> Bool)
-> (InstrumentationLibrary -> InstrumentationLibrary -> Bool)
-> Eq InstrumentationLibrary
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InstrumentationLibrary -> InstrumentationLibrary -> Bool
$c/= :: InstrumentationLibrary -> InstrumentationLibrary -> Bool
== :: InstrumentationLibrary -> InstrumentationLibrary -> Bool
$c== :: InstrumentationLibrary -> InstrumentationLibrary -> Bool
Eq, (forall x. InstrumentationLibrary -> Rep InstrumentationLibrary x)
-> (forall x.
Rep InstrumentationLibrary x -> InstrumentationLibrary)
-> Generic InstrumentationLibrary
forall x. Rep InstrumentationLibrary x -> InstrumentationLibrary
forall x. InstrumentationLibrary -> Rep InstrumentationLibrary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InstrumentationLibrary x -> InstrumentationLibrary
$cfrom :: forall x. InstrumentationLibrary -> Rep InstrumentationLibrary x
Generic, Int -> InstrumentationLibrary -> ShowS
[InstrumentationLibrary] -> ShowS
InstrumentationLibrary -> String
(Int -> InstrumentationLibrary -> ShowS)
-> (InstrumentationLibrary -> String)
-> ([InstrumentationLibrary] -> ShowS)
-> Show InstrumentationLibrary
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InstrumentationLibrary] -> ShowS
$cshowList :: [InstrumentationLibrary] -> ShowS
show :: InstrumentationLibrary -> String
$cshow :: InstrumentationLibrary -> String
showsPrec :: Int -> InstrumentationLibrary -> ShowS
$cshowsPrec :: Int -> InstrumentationLibrary -> ShowS
Show)
instance Hashable InstrumentationLibrary
instance IsString InstrumentationLibrary where
fromString :: String -> InstrumentationLibrary
fromString String
str = Text -> Text -> InstrumentationLibrary
InstrumentationLibrary (String -> Text
forall a. IsString a => String -> a
fromString String
str) Text
""
data Exporter a = Exporter
{ Exporter a
-> HashMap InstrumentationLibrary (Vector a) -> IO ExportResult
exporterExport :: HashMap InstrumentationLibrary (Vector a) -> IO ExportResult
, Exporter a -> IO ()
exporterShutdown :: IO ()
}
data ShutdownResult = ShutdownSuccess | ShutdownFailure | ShutdownTimeout
data Processor = Processor
{ Processor -> IORef ImmutableSpan -> Context -> IO ()
processorOnStart :: IORef ImmutableSpan -> Context -> IO ()
, Processor -> IORef ImmutableSpan -> IO ()
processorOnEnd :: IORef ImmutableSpan -> IO ()
, Processor -> IO (Async ShutdownResult)
processorShutdown :: IO (Async ShutdownResult)
, Processor -> IO ()
processorForceFlush :: IO ()
}
data TracerProvider = TracerProvider
{ TracerProvider -> Vector Processor
tracerProviderProcessors :: !(Vector Processor)
, TracerProvider -> IdGenerator
tracerProviderIdGenerator :: !IdGenerator
, TracerProvider -> Sampler
tracerProviderSampler :: !Sampler
, TracerProvider -> MaterializedResources
tracerProviderResources :: !MaterializedResources
, TracerProvider -> AttributeLimits
tracerProviderAttributeLimits :: !AttributeLimits
, TracerProvider -> SpanLimits
tracerProviderSpanLimits :: !SpanLimits
, TracerProvider -> Propagator Context RequestHeaders RequestHeaders
tracerProviderPropagators :: !(Propagator Context RequestHeaders ResponseHeaders)
, TracerProvider -> Log Text -> IO ()
tracerProviderLogger :: Log Text -> IO ()
}
data Tracer = Tracer
{ Tracer -> InstrumentationLibrary
tracerName :: {-# UNPACK #-} !InstrumentationLibrary
, Tracer -> TracerProvider
tracerProvider :: !TracerProvider
}
instance Show Tracer where
show :: Tracer -> String
show Tracer {tracerName :: Tracer -> InstrumentationLibrary
tracerName = InstrumentationLibrary
name} = String
"Tracer { tracerName = " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> InstrumentationLibrary -> String
forall a. Show a => a -> String
show InstrumentationLibrary
name String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"}"
data NewLink = NewLink
{ NewLink -> SpanContext
linkContext :: !SpanContext
, NewLink -> [(Text, Attribute)]
linkAttributes :: [(Text, Attribute)]
}
deriving (Int -> NewLink -> ShowS
[NewLink] -> ShowS
NewLink -> String
(Int -> NewLink -> ShowS)
-> (NewLink -> String) -> ([NewLink] -> ShowS) -> Show NewLink
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NewLink] -> ShowS
$cshowList :: [NewLink] -> ShowS
show :: NewLink -> String
$cshow :: NewLink -> String
showsPrec :: Int -> NewLink -> ShowS
$cshowsPrec :: Int -> NewLink -> ShowS
Show)
data Link = Link
{ Link -> SpanContext
frozenLinkContext :: !SpanContext
, Link -> Attributes
frozenLinkAttributes :: Attributes
}
deriving (Int -> Link -> ShowS
[Link] -> ShowS
Link -> String
(Int -> Link -> ShowS)
-> (Link -> String) -> ([Link] -> ShowS) -> Show Link
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Link] -> ShowS
$cshowList :: [Link] -> ShowS
show :: Link -> String
$cshow :: Link -> String
showsPrec :: Int -> Link -> ShowS
$cshowsPrec :: Int -> Link -> ShowS
Show)
data SpanArguments = SpanArguments
{ SpanArguments -> SpanKind
kind :: SpanKind
, SpanArguments -> [(Text, Attribute)]
attributes :: [(Text, Attribute)]
, SpanArguments -> [NewLink]
links :: [NewLink]
, SpanArguments -> Maybe Timestamp
startTime :: Maybe Timestamp
}
data FlushResult
= FlushTimeout
| FlushSuccess
| FlushError
deriving (Int -> FlushResult -> ShowS
[FlushResult] -> ShowS
FlushResult -> String
(Int -> FlushResult -> ShowS)
-> (FlushResult -> String)
-> ([FlushResult] -> ShowS)
-> Show FlushResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FlushResult] -> ShowS
$cshowList :: [FlushResult] -> ShowS
show :: FlushResult -> String
$cshow :: FlushResult -> String
showsPrec :: Int -> FlushResult -> ShowS
$cshowsPrec :: Int -> FlushResult -> ShowS
Show)
data SpanKind
= Server
| Client
| Producer
| Consumer
| Internal
deriving (Int -> SpanKind -> ShowS
[SpanKind] -> ShowS
SpanKind -> String
(Int -> SpanKind -> ShowS)
-> (SpanKind -> String) -> ([SpanKind] -> ShowS) -> Show SpanKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SpanKind] -> ShowS
$cshowList :: [SpanKind] -> ShowS
show :: SpanKind -> String
$cshow :: SpanKind -> String
showsPrec :: Int -> SpanKind -> ShowS
$cshowsPrec :: Int -> SpanKind -> ShowS
Show)
data SpanStatus
= Unset
| Error Text
| Ok
deriving (Int -> SpanStatus -> ShowS
[SpanStatus] -> ShowS
SpanStatus -> String
(Int -> SpanStatus -> ShowS)
-> (SpanStatus -> String)
-> ([SpanStatus] -> ShowS)
-> Show SpanStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SpanStatus] -> ShowS
$cshowList :: [SpanStatus] -> ShowS
show :: SpanStatus -> String
$cshow :: SpanStatus -> String
showsPrec :: Int -> SpanStatus -> ShowS
$cshowsPrec :: Int -> SpanStatus -> ShowS
Show, SpanStatus -> SpanStatus -> Bool
(SpanStatus -> SpanStatus -> Bool)
-> (SpanStatus -> SpanStatus -> Bool) -> Eq SpanStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SpanStatus -> SpanStatus -> Bool
$c/= :: SpanStatus -> SpanStatus -> Bool
== :: SpanStatus -> SpanStatus -> Bool
$c== :: SpanStatus -> SpanStatus -> Bool
Eq)
instance Ord SpanStatus where
compare :: SpanStatus -> SpanStatus -> Ordering
compare SpanStatus
Unset SpanStatus
Unset = Ordering
EQ
compare SpanStatus
Unset (Error Text
_) = Ordering
LT
compare SpanStatus
Unset SpanStatus
Ok = Ordering
LT
compare (Error Text
_) SpanStatus
Unset = Ordering
GT
compare (Error Text
_) (Error Text
_) = Ordering
GT
compare (Error Text
_) SpanStatus
Ok = Ordering
LT
compare SpanStatus
Ok SpanStatus
Unset = Ordering
GT
compare SpanStatus
Ok (Error Text
_) = Ordering
GT
compare SpanStatus
Ok SpanStatus
Ok = Ordering
EQ
data ImmutableSpan = ImmutableSpan
{ ImmutableSpan -> Text
spanName :: Text
, ImmutableSpan -> Maybe Span
spanParent :: Maybe Span
, ImmutableSpan -> SpanContext
spanContext :: SpanContext
, ImmutableSpan -> SpanKind
spanKind :: SpanKind
, ImmutableSpan -> Timestamp
spanStart :: Timestamp
, ImmutableSpan -> Maybe Timestamp
spanEnd :: Maybe Timestamp
, ImmutableSpan -> Attributes
spanAttributes :: Attributes
, ImmutableSpan -> FrozenBoundedCollection Link
spanLinks :: FrozenBoundedCollection Link
, ImmutableSpan -> AppendOnlyBoundedCollection Event
spanEvents :: AppendOnlyBoundedCollection Event
, ImmutableSpan -> SpanStatus
spanStatus :: SpanStatus
, ImmutableSpan -> Tracer
spanTracer :: Tracer
} deriving (Int -> ImmutableSpan -> ShowS
[ImmutableSpan] -> ShowS
ImmutableSpan -> String
(Int -> ImmutableSpan -> ShowS)
-> (ImmutableSpan -> String)
-> ([ImmutableSpan] -> ShowS)
-> Show ImmutableSpan
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImmutableSpan] -> ShowS
$cshowList :: [ImmutableSpan] -> ShowS
show :: ImmutableSpan -> String
$cshow :: ImmutableSpan -> String
showsPrec :: Int -> ImmutableSpan -> ShowS
$cshowsPrec :: Int -> ImmutableSpan -> ShowS
Show)
data Span
= Span (IORef ImmutableSpan)
| FrozenSpan SpanContext
| Dropped SpanContext
instance Show Span where
show :: Span -> String
show (Span IORef ImmutableSpan
_ioref) = String
"(mutable span)"
show (FrozenSpan SpanContext
ctx) = SpanContext -> String
forall a. Show a => a -> String
show SpanContext
ctx
show (Dropped SpanContext
ctx) = SpanContext -> String
forall a. Show a => a -> String
show SpanContext
ctx
defaultTraceFlags :: TraceFlags
defaultTraceFlags :: TraceFlags
defaultTraceFlags = Word8 -> TraceFlags
TraceFlags Word8
0
isSampled :: TraceFlags -> Bool
isSampled :: TraceFlags -> Bool
isSampled (TraceFlags Word8
flags) = Word8
flags Word8 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
`testBit` Int
0
setSampled :: TraceFlags -> TraceFlags
setSampled :: TraceFlags -> TraceFlags
setSampled (TraceFlags Word8
flags) = Word8 -> TraceFlags
TraceFlags (Word8
flags Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`setBit` Int
0)
unsetSampled :: TraceFlags -> TraceFlags
unsetSampled :: TraceFlags -> TraceFlags
unsetSampled (TraceFlags Word8
flags) = Word8 -> TraceFlags
TraceFlags (Word8
flags Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`clearBit` Int
0)
traceFlagsValue :: TraceFlags -> Word8
traceFlagsValue :: TraceFlags -> Word8
traceFlagsValue (TraceFlags Word8
flags) = Word8
flags
traceFlagsFromWord8 :: Word8 -> TraceFlags
traceFlagsFromWord8 :: Word8 -> TraceFlags
traceFlagsFromWord8 = Word8 -> TraceFlags
TraceFlags
data SpanContext = SpanContext
{ SpanContext -> TraceFlags
traceFlags :: TraceFlags
, SpanContext -> Bool
isRemote :: Bool
, SpanContext -> TraceId
traceId :: TraceId
, SpanContext -> SpanId
spanId :: SpanId
, SpanContext -> TraceState
traceState :: TraceState
} deriving (Int -> SpanContext -> ShowS
[SpanContext] -> ShowS
SpanContext -> String
(Int -> SpanContext -> ShowS)
-> (SpanContext -> String)
-> ([SpanContext] -> ShowS)
-> Show SpanContext
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SpanContext] -> ShowS
$cshowList :: [SpanContext] -> ShowS
show :: SpanContext -> String
$cshow :: SpanContext -> String
showsPrec :: Int -> SpanContext -> ShowS
$cshowsPrec :: Int -> SpanContext -> ShowS
Show, SpanContext -> SpanContext -> Bool
(SpanContext -> SpanContext -> Bool)
-> (SpanContext -> SpanContext -> Bool) -> Eq SpanContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SpanContext -> SpanContext -> Bool
$c/= :: SpanContext -> SpanContext -> Bool
== :: SpanContext -> SpanContext -> Bool
$c== :: SpanContext -> SpanContext -> Bool
Eq)
newtype NonRecordingSpan = NonRecordingSpan SpanContext
data NewEvent = NewEvent
{ NewEvent -> Text
newEventName :: Text
, NewEvent -> [(Text, Attribute)]
newEventAttributes :: [(Text, Attribute)]
, NewEvent -> Maybe Timestamp
newEventTimestamp :: Maybe Timestamp
}
data Event = Event
{ Event -> Text
eventName :: Text
, Event -> Attributes
eventAttributes :: Attributes
, Event -> Timestamp
eventTimestamp :: Timestamp
}
deriving (Int -> Event -> ShowS
[Event] -> ShowS
Event -> String
(Int -> Event -> ShowS)
-> (Event -> String) -> ([Event] -> ShowS) -> Show Event
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Event] -> ShowS
$cshowList :: [Event] -> ShowS
show :: Event -> String
$cshow :: Event -> String
showsPrec :: Int -> Event -> ShowS
$cshowsPrec :: Int -> Event -> ShowS
Show)
class ToEvent a where
toEvent :: a -> Event
data SamplingResult
= Drop
| RecordOnly
| RecordAndSample
deriving (Int -> SamplingResult -> ShowS
[SamplingResult] -> ShowS
SamplingResult -> String
(Int -> SamplingResult -> ShowS)
-> (SamplingResult -> String)
-> ([SamplingResult] -> ShowS)
-> Show SamplingResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SamplingResult] -> ShowS
$cshowList :: [SamplingResult] -> ShowS
show :: SamplingResult -> String
$cshow :: SamplingResult -> String
showsPrec :: Int -> SamplingResult -> ShowS
$cshowsPrec :: Int -> SamplingResult -> ShowS
Show, SamplingResult -> SamplingResult -> Bool
(SamplingResult -> SamplingResult -> Bool)
-> (SamplingResult -> SamplingResult -> Bool) -> Eq SamplingResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SamplingResult -> SamplingResult -> Bool
$c/= :: SamplingResult -> SamplingResult -> Bool
== :: SamplingResult -> SamplingResult -> Bool
$c== :: SamplingResult -> SamplingResult -> Bool
Eq)
data Sampler = Sampler
{ Sampler -> Text
getDescription :: Text
, Sampler
-> Context
-> TraceId
-> Text
-> SpanArguments
-> IO (SamplingResult, [(Text, Attribute)], TraceState)
shouldSample :: Context -> TraceId -> Text -> SpanArguments -> IO (SamplingResult, [(Text, Attribute)], TraceState)
}
data SpanLimits = SpanLimits
{ SpanLimits -> Maybe Int
spanAttributeValueLengthLimit :: Maybe Int
, SpanLimits -> Maybe Int
spanAttributeCountLimit :: Maybe Int
, SpanLimits -> Maybe Int
eventCountLimit :: Maybe Int
, SpanLimits -> Maybe Int
eventAttributeCountLimit :: Maybe Int
, SpanLimits -> Maybe Int
linkCountLimit :: Maybe Int
, SpanLimits -> Maybe Int
linkAttributeCountLimit :: Maybe Int
} deriving (Int -> SpanLimits -> ShowS
[SpanLimits] -> ShowS
SpanLimits -> String
(Int -> SpanLimits -> ShowS)
-> (SpanLimits -> String)
-> ([SpanLimits] -> ShowS)
-> Show SpanLimits
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SpanLimits] -> ShowS
$cshowList :: [SpanLimits] -> ShowS
show :: SpanLimits -> String
$cshow :: SpanLimits -> String
showsPrec :: Int -> SpanLimits -> ShowS
$cshowsPrec :: Int -> SpanLimits -> ShowS
Show, SpanLimits -> SpanLimits -> Bool
(SpanLimits -> SpanLimits -> Bool)
-> (SpanLimits -> SpanLimits -> Bool) -> Eq SpanLimits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SpanLimits -> SpanLimits -> Bool
$c/= :: SpanLimits -> SpanLimits -> Bool
== :: SpanLimits -> SpanLimits -> Bool
$c== :: SpanLimits -> SpanLimits -> Bool
Eq)
defaultSpanLimits :: SpanLimits
defaultSpanLimits :: SpanLimits
defaultSpanLimits = Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> SpanLimits
SpanLimits
Maybe Int
forall a. Maybe a
Nothing
Maybe Int
forall a. Maybe a
Nothing
Maybe Int
forall a. Maybe a
Nothing
Maybe Int
forall a. Maybe a
Nothing
Maybe Int
forall a. Maybe a
Nothing
Maybe Int
forall a. Maybe a
Nothing
type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t
type Lens' s a = Lens s s a a
getSpanContext :: MonadIO m => Span -> m SpanContext
getSpanContext :: Span -> m SpanContext
getSpanContext (Span IORef ImmutableSpan
s) = IO SpanContext -> m SpanContext
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (ImmutableSpan -> SpanContext
spanContext (ImmutableSpan -> SpanContext)
-> IO ImmutableSpan -> IO SpanContext
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IORef ImmutableSpan -> IO ImmutableSpan
forall a. IORef a -> IO a
readIORef IORef ImmutableSpan
s)
getSpanContext (FrozenSpan SpanContext
c) = SpanContext -> m SpanContext
forall (f :: * -> *) a. Applicative f => a -> f a
pure SpanContext
c
getSpanContext (Dropped SpanContext
c) = SpanContext -> m SpanContext
forall (f :: * -> *) a. Applicative f => a -> f a
pure SpanContext
c