| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
OpenTracing.Propagation
Description
Types and functions for serializing and deserializing SpanContexts across
process boundaries.
One of the big motiviating use cases for propagation is for tracing distributed executions through RPC calls.
Synopsis
- type TextMap = HashMap Text Text
- type Headers = [Header]
- type Propagation carriers = Rec Carrier carriers
- class HasPropagation a p | a -> p where- propagation :: Getting r a (Propagation p)
 
- newtype Carrier a = Carrier {- fromCarrier :: Prism' a SpanContext
 
- type HasCarrier c cs = c ∈ cs
- type HasCarriers cs ds = cs ⊆ ds
- carrier :: (HasCarrier c cs, HasPropagation r cs) => proxy c -> r -> Prism' c SpanContext
- inject :: forall c r p. (HasCarrier c p, HasPropagation r p) => r -> SpanContext -> c
- extract :: forall c r p. (HasCarrier c p, HasPropagation r p) => r -> c -> Maybe SpanContext
- otPropagation :: Propagation '[TextMap, Headers]
- b3Propagation :: Propagation '[TextMap, Headers]
- _OTTextMap :: Prism' TextMap SpanContext
- _OTHeaders :: Prism' Headers SpanContext
- _B3TextMap :: Prism' TextMap SpanContext
- _B3Headers :: Prism' Headers SpanContext
- _HeadersTextMap :: Iso' Headers TextMap
- data Rec (a :: u -> Type) (b :: [u]) where
- rappend :: forall k (f :: k -> Type) (as :: [k]) (bs :: [k]). Rec f as -> Rec f bs -> Rec f (as ++ bs)
- (<+>) :: forall k (f :: k -> Type) (as :: [k]) (bs :: [k]). Rec f as -> Rec f bs -> Rec f (as ++ bs)
- rcast :: forall k1 k2 (rs :: [k1]) (ss :: [k1]) (f :: k2 -> Type) record (is :: [Nat]). (RecSubset record rs ss is, RecSubsetFCtx record f) => record f ss -> record f rs
Documentation
type Propagation carriers = Rec Carrier carriers Source #
A Propagation contains the different ways that a SpanContext can be
 serialized and deserialized. For example Propagation '[TextMap, Headers] indicates
 support for serializing to Header or to TextMap.
Since: 0.1.0.0
class HasPropagation a p | a -> p where Source #
A typeclass for application environments that contain a Propagation.
Since: 0.1.0.0
Methods
propagation :: Getting r a (Propagation p) Source #
Instances
| HasPropagation (Propagation p) p Source # | |
| Defined in OpenTracing.Propagation Methods propagation :: Getting r (Propagation p) (Propagation p) Source # | |
`Carrier a` is a way to convert a SpanContext into or from an a.
Since: 0.1.0.0
Constructors
| Carrier | |
| Fields 
 | |
Instances
| HasPropagation (Propagation p) p Source # | |
| Defined in OpenTracing.Propagation Methods propagation :: Getting r (Propagation p) (Propagation p) Source # | |
type HasCarrier c cs = c ∈ cs Source #
type HasCarriers cs ds = cs ⊆ ds Source #
Arguments
| :: (HasCarrier c cs, HasPropagation r cs) | |
| => proxy c | Proxy for the carrier type  | 
| -> r | The application context | 
| -> Prism' c SpanContext | 
Retrieve a (de)serialization lens from the application context for
 format c.
Since: 0.1.0.0
inject :: forall c r p. (HasCarrier c p, HasPropagation r p) => r -> SpanContext -> c Source #
Serialize a SpanContext into the format c using a serializer from
 the application context.
Since: 0.1.0.0
extract :: forall c r p. (HasCarrier c p, HasPropagation r p) => r -> c -> Maybe SpanContext Source #
Attempt to deserialize a SpanContext from the format c using a deserializer
 from the application context
Since: 0.1.0.0
otPropagation :: Propagation '[TextMap, Headers] Source #
A propagation using an "ot" prefix. No parent span id is propagated in OT.
b3Propagation :: Propagation '[TextMap, Headers] Source #
A propagation using an "x-b3" prefix for use with Zipkin.
Re-exports from Vinyl
data Rec (a :: u -> Type) (b :: [u]) where #
A record is parameterized by a universe u, an interpretation f and a
 list of rows rs.  The labels or indices of the record are given by
 inhabitants of the kind u; the type of values at any label r :: u is
 given by its interpretation f r :: *.
Constructors
| RNil :: forall u (a :: u -> Type). Rec a ('[] :: [u]) | |
| (:&) :: forall u (a :: u -> Type) (r :: u) (rs :: [u]). !(a r) -> !(Rec a rs) -> Rec a (r ': rs) infixr 7 | 
Instances
| RecSubset (Rec :: (k -> Type) -> [k] -> Type) ('[] :: [k]) (ss :: [k]) ('[] :: [Nat]) | |
| Defined in Data.Vinyl.Lens Associated Types type RecSubsetFCtx Rec f # Methods rsubsetC :: forall g (f :: k0 -> Type). (Functor g, RecSubsetFCtx Rec f) => (Rec f '[] -> g (Rec f '[])) -> Rec f ss -> g (Rec f ss) # rcastC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f ss -> Rec f '[] # rreplaceC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f '[] -> Rec f ss -> Rec f ss # | |
| (RElem r ss i, RSubset rs ss is) => RecSubset (Rec :: (k -> Type) -> [k] -> Type) (r ': rs :: [k]) (ss :: [k]) (i ': is) | |
| Defined in Data.Vinyl.Lens Associated Types type RecSubsetFCtx Rec f # Methods rsubsetC :: forall g (f :: k0 -> Type). (Functor g, RecSubsetFCtx Rec f) => (Rec f (r ': rs) -> g (Rec f (r ': rs))) -> Rec f ss -> g (Rec f ss) # rcastC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f ss -> Rec f (r ': rs) # rreplaceC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f (r ': rs) -> Rec f ss -> Rec f ss # | |
| RecElem (Rec :: (a -> Type) -> [a] -> Type) (r :: a) (r' :: a) (r ': rs :: [a]) (r' ': rs :: [a]) 'Z | |
| Defined in Data.Vinyl.Lens Associated Types type RecElemFCtx Rec f # | |
| (RIndex r (s ': rs) ~ 'S i, RecElem (Rec :: (a -> Type) -> [a] -> Type) r r' rs rs' i) => RecElem (Rec :: (a -> Type) -> [a] -> Type) (r :: a) (r' :: a) (s ': rs :: [a]) (s ': rs' :: [a]) ('S i) | |
| Defined in Data.Vinyl.Lens Associated Types type RecElemFCtx Rec f # | |
| HasPropagation (Propagation p) p Source # | |
| Defined in OpenTracing.Propagation Methods propagation :: Getting r (Propagation p) (Propagation p) Source # | |
| TestCoercion f => TestCoercion (Rec f :: [u] -> Type) | |
| Defined in Data.Vinyl.Core | |
| TestEquality f => TestEquality (Rec f :: [u] -> Type) | |
| Defined in Data.Vinyl.Core | |
| Eq (Rec f ('[] :: [u])) | |
| (Eq (f r), Eq (Rec f rs)) => Eq (Rec f (r ': rs)) | |
| Ord (Rec f ('[] :: [u])) | |
| (Ord (f r), Ord (Rec f rs)) => Ord (Rec f (r ': rs)) | |
| Defined in Data.Vinyl.Core Methods compare :: Rec f (r ': rs) -> Rec f (r ': rs) -> Ordering # (<) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool # (<=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool # (>) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool # (>=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool # max :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) # min :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) # | |
| (RMap rs, ReifyConstraint Show f rs, RecordToList rs) => Show (Rec f rs) | Records may be shown insofar as their points may be shown.
  | 
| Generic (Rec f ('[] :: [u])) | |
| Generic (Rec f rs) => Generic (Rec f (r ': rs)) | |
| Semigroup (Rec f ('[] :: [u])) | |
| (Semigroup (f r), Semigroup (Rec f rs)) => Semigroup (Rec f (r ': rs)) | |
| Monoid (Rec f ('[] :: [u])) | |
| (Monoid (f r), Monoid (Rec f rs)) => Monoid (Rec f (r ': rs)) | |
| Storable (Rec f ('[] :: [u])) | |
| Defined in Data.Vinyl.Core | |
| (Storable (f r), Storable (Rec f rs)) => Storable (Rec f (r ': rs)) | |
| Defined in Data.Vinyl.Core Methods sizeOf :: Rec f (r ': rs) -> Int # alignment :: Rec f (r ': rs) -> Int # peekElemOff :: Ptr (Rec f (r ': rs)) -> Int -> IO (Rec f (r ': rs)) # pokeElemOff :: Ptr (Rec f (r ': rs)) -> Int -> Rec f (r ': rs) -> IO () # peekByteOff :: Ptr b -> Int -> IO (Rec f (r ': rs)) # pokeByteOff :: Ptr b -> Int -> Rec f (r ': rs) -> IO () # | |
| ReifyConstraint NFData f xs => NFData (Rec f xs) | |
| Defined in Data.Vinyl.Core | |
| type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) | |
| Defined in Data.Vinyl.Lens | |
| type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) | |
| Defined in Data.Vinyl.Lens | |
| type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) | |
| Defined in Data.Vinyl.Lens | |
| type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) | |
| Defined in Data.Vinyl.Lens | |
| type Rep (Rec f (r ': rs)) | |
| Defined in Data.Vinyl.Core type Rep (Rec f (r ': rs)) = C1 ('MetaCons ":&" ('InfixI 'RightAssociative 7) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f r)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rep (Rec f rs))) | |
| type Rep (Rec f ('[] :: [u])) | |
| Defined in Data.Vinyl.Core | |
rappend :: forall k (f :: k -> Type) (as :: [k]) (bs :: [k]). Rec f as -> Rec f bs -> Rec f (as ++ bs) #
Two records may be pasted together.
(<+>) :: forall k (f :: k -> Type) (as :: [k]) (bs :: [k]). Rec f as -> Rec f bs -> Rec f (as ++ bs) infixr 5 #
A shorthand for rappend.
rcast :: forall k1 k2 (rs :: [k1]) (ss :: [k1]) (f :: k2 -> Type) record (is :: [Nat]). (RecSubset record rs ss is, RecSubsetFCtx record f) => record f ss -> record f rs #
Takes a larger record to a smaller one by forgetting fields. This
 is rcastC with the type arguments reordered for more convenient
 usage with TypeApplications.