{-# LANGUAGE RankNTypes #-}
module OpenTelemetry.Propagator where
import Control.Monad
import Control.Monad.IO.Class
import Data.Text
data Propagator context inboundCarrier outboundCarrier = Propagator
{ forall context inboundCarrier outboundCarrier.
Propagator context inboundCarrier outboundCarrier -> [Text]
propagatorNames :: [Text]
, :: inboundCarrier -> context -> IO context
, forall context inboundCarrier outboundCarrier.
Propagator context inboundCarrier outboundCarrier
-> context -> outboundCarrier -> IO outboundCarrier
injector :: context -> outboundCarrier -> IO outboundCarrier
}
instance Semigroup (Propagator c i o) where
(Propagator [Text]
lNames i -> c -> IO c
lExtract c -> o -> IO o
lInject) <> :: Propagator c i o -> Propagator c i o -> Propagator c i o
<> (Propagator [Text]
rNames i -> c -> IO c
rExtract c -> o -> IO o
rInject) =
Propagator
{ propagatorNames :: [Text]
propagatorNames = [Text]
lNames forall a. Semigroup a => a -> a -> a
<> [Text]
rNames
, extractor :: i -> c -> IO c
extractor = \i
i -> i -> c -> IO c
lExtract i
i forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> i -> c -> IO c
rExtract i
i
, injector :: c -> o -> IO o
injector = \c
c -> c -> o -> IO o
lInject c
c forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> c -> o -> IO o
rInject c
c
}
instance Monoid (Propagator c i o) where
mempty :: Propagator c i o
mempty = forall context inboundCarrier outboundCarrier.
[Text]
-> (inboundCarrier -> context -> IO context)
-> (context -> outboundCarrier -> IO outboundCarrier)
-> Propagator context inboundCarrier outboundCarrier
Propagator forall a. Monoid a => a
mempty (\i
_ c
c -> forall (f :: * -> *) a. Applicative f => a -> f a
pure c
c) (\c
_ o
p -> forall (f :: * -> *) a. Applicative f => a -> f a
pure o
p)
extract ::
(MonadIO m) =>
Propagator context i o ->
i ->
context ->
m context
(Propagator [Text]
_ i -> context -> IO context
extractor context -> o -> IO o
_) i
i = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> context -> IO context
extractor i
i
inject ::
(MonadIO m) =>
Propagator context i o ->
context ->
o ->
m o
inject :: forall (m :: * -> *) context i o.
MonadIO m =>
Propagator context i o -> context -> o -> m o
inject (Propagator [Text]
_ i -> context -> IO context
_ context -> o -> IO o
injector) context
c = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. context -> o -> IO o
injector context
c