{- This file was auto-generated from opentelemetry/proto/trace/v1/trace.proto by the proto-lens-protoc program. -}
{-# LANGUAGE ScopedTypeVariables, DataKinds, TypeFamilies, UndecidableInstances, GeneralizedNewtypeDeriving, MultiParamTypeClasses, FlexibleContexts, FlexibleInstances, PatternSynonyms, MagicHash, NoImplicitPrelude, DataKinds, BangPatterns, TypeApplications, OverloadedStrings, DerivingStrategies#-}
{-# OPTIONS_GHC -Wno-unused-imports#-}
{-# OPTIONS_GHC -Wno-duplicate-exports#-}
{-# OPTIONS_GHC -Wno-dodgy-exports#-}
module Proto.Opentelemetry.Proto.Trace.V1.Trace (
        InstrumentationLibrarySpans(), ResourceSpans(), Span(),
        Span'Event(), Span'Link(), Span'SpanKind(..), Span'SpanKind(),
        Span'SpanKind'UnrecognizedValue, Status(),
        Status'DeprecatedStatusCode(..), Status'DeprecatedStatusCode(),
        Status'DeprecatedStatusCode'UnrecognizedValue,
        Status'StatusCode(..), Status'StatusCode(),
        Status'StatusCode'UnrecognizedValue, TracesData()
    ) where
import qualified Data.ProtoLens.Runtime.Control.DeepSeq as Control.DeepSeq
import qualified Data.ProtoLens.Runtime.Data.ProtoLens.Prism as Data.ProtoLens.Prism
import qualified Data.ProtoLens.Runtime.Prelude as Prelude
import qualified Data.ProtoLens.Runtime.Data.Int as Data.Int
import qualified Data.ProtoLens.Runtime.Data.Monoid as Data.Monoid
import qualified Data.ProtoLens.Runtime.Data.Word as Data.Word
import qualified Data.ProtoLens.Runtime.Data.ProtoLens as Data.ProtoLens
import qualified Data.ProtoLens.Runtime.Data.ProtoLens.Encoding.Bytes as Data.ProtoLens.Encoding.Bytes
import qualified Data.ProtoLens.Runtime.Data.ProtoLens.Encoding.Growing as Data.ProtoLens.Encoding.Growing
import qualified Data.ProtoLens.Runtime.Data.ProtoLens.Encoding.Parser.Unsafe as Data.ProtoLens.Encoding.Parser.Unsafe
import qualified Data.ProtoLens.Runtime.Data.ProtoLens.Encoding.Wire as Data.ProtoLens.Encoding.Wire
import qualified Data.ProtoLens.Runtime.Data.ProtoLens.Field as Data.ProtoLens.Field
import qualified Data.ProtoLens.Runtime.Data.ProtoLens.Message.Enum as Data.ProtoLens.Message.Enum
import qualified Data.ProtoLens.Runtime.Data.ProtoLens.Service.Types as Data.ProtoLens.Service.Types
import qualified Data.ProtoLens.Runtime.Lens.Family2 as Lens.Family2
import qualified Data.ProtoLens.Runtime.Lens.Family2.Unchecked as Lens.Family2.Unchecked
import qualified Data.ProtoLens.Runtime.Data.Text as Data.Text
import qualified Data.ProtoLens.Runtime.Data.Map as Data.Map
import qualified Data.ProtoLens.Runtime.Data.ByteString as Data.ByteString
import qualified Data.ProtoLens.Runtime.Data.ByteString.Char8 as Data.ByteString.Char8
import qualified Data.ProtoLens.Runtime.Data.Text.Encoding as Data.Text.Encoding
import qualified Data.ProtoLens.Runtime.Data.Vector as Data.Vector
import qualified Data.ProtoLens.Runtime.Data.Vector.Generic as Data.Vector.Generic
import qualified Data.ProtoLens.Runtime.Data.Vector.Unboxed as Data.Vector.Unboxed
import qualified Data.ProtoLens.Runtime.Text.Read as Text.Read
import qualified Proto.Opentelemetry.Proto.Common.V1.Common
import qualified Proto.Opentelemetry.Proto.Resource.V1.Resource
{- | Fields :
     
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.instrumentationLibrary' @:: Lens' InstrumentationLibrarySpans Proto.Opentelemetry.Proto.Common.V1.Common.InstrumentationLibrary@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.maybe'instrumentationLibrary' @:: Lens' InstrumentationLibrarySpans (Prelude.Maybe Proto.Opentelemetry.Proto.Common.V1.Common.InstrumentationLibrary)@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.spans' @:: Lens' InstrumentationLibrarySpans [Span]@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.vec'spans' @:: Lens' InstrumentationLibrarySpans (Data.Vector.Vector Span)@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.schemaUrl' @:: Lens' InstrumentationLibrarySpans Data.Text.Text@ -}
data InstrumentationLibrarySpans
  = InstrumentationLibrarySpans'_constructor {InstrumentationLibrarySpans -> Maybe InstrumentationLibrary
_InstrumentationLibrarySpans'instrumentationLibrary :: !(Prelude.Maybe Proto.Opentelemetry.Proto.Common.V1.Common.InstrumentationLibrary),
                                              InstrumentationLibrarySpans -> Vector Span
_InstrumentationLibrarySpans'spans :: !(Data.Vector.Vector Span),
                                              InstrumentationLibrarySpans -> Text
_InstrumentationLibrarySpans'schemaUrl :: !Data.Text.Text,
                                              InstrumentationLibrarySpans -> FieldSet
_InstrumentationLibrarySpans'_unknownFields :: !Data.ProtoLens.FieldSet}
  deriving stock (InstrumentationLibrarySpans -> InstrumentationLibrarySpans -> Bool
(InstrumentationLibrarySpans
 -> InstrumentationLibrarySpans -> Bool)
-> (InstrumentationLibrarySpans
    -> InstrumentationLibrarySpans -> Bool)
-> Eq InstrumentationLibrarySpans
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InstrumentationLibrarySpans -> InstrumentationLibrarySpans -> Bool
$c/= :: InstrumentationLibrarySpans -> InstrumentationLibrarySpans -> Bool
== :: InstrumentationLibrarySpans -> InstrumentationLibrarySpans -> Bool
$c== :: InstrumentationLibrarySpans -> InstrumentationLibrarySpans -> Bool
Prelude.Eq, Eq InstrumentationLibrarySpans
Eq InstrumentationLibrarySpans
-> (InstrumentationLibrarySpans
    -> InstrumentationLibrarySpans -> Ordering)
-> (InstrumentationLibrarySpans
    -> InstrumentationLibrarySpans -> Bool)
-> (InstrumentationLibrarySpans
    -> InstrumentationLibrarySpans -> Bool)
-> (InstrumentationLibrarySpans
    -> InstrumentationLibrarySpans -> Bool)
-> (InstrumentationLibrarySpans
    -> InstrumentationLibrarySpans -> Bool)
-> (InstrumentationLibrarySpans
    -> InstrumentationLibrarySpans -> InstrumentationLibrarySpans)
-> (InstrumentationLibrarySpans
    -> InstrumentationLibrarySpans -> InstrumentationLibrarySpans)
-> Ord InstrumentationLibrarySpans
InstrumentationLibrarySpans -> InstrumentationLibrarySpans -> Bool
InstrumentationLibrarySpans
-> InstrumentationLibrarySpans -> Ordering
InstrumentationLibrarySpans
-> InstrumentationLibrarySpans -> InstrumentationLibrarySpans
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 :: InstrumentationLibrarySpans
-> InstrumentationLibrarySpans -> InstrumentationLibrarySpans
$cmin :: InstrumentationLibrarySpans
-> InstrumentationLibrarySpans -> InstrumentationLibrarySpans
max :: InstrumentationLibrarySpans
-> InstrumentationLibrarySpans -> InstrumentationLibrarySpans
$cmax :: InstrumentationLibrarySpans
-> InstrumentationLibrarySpans -> InstrumentationLibrarySpans
>= :: InstrumentationLibrarySpans -> InstrumentationLibrarySpans -> Bool
$c>= :: InstrumentationLibrarySpans -> InstrumentationLibrarySpans -> Bool
> :: InstrumentationLibrarySpans -> InstrumentationLibrarySpans -> Bool
$c> :: InstrumentationLibrarySpans -> InstrumentationLibrarySpans -> Bool
<= :: InstrumentationLibrarySpans -> InstrumentationLibrarySpans -> Bool
$c<= :: InstrumentationLibrarySpans -> InstrumentationLibrarySpans -> Bool
< :: InstrumentationLibrarySpans -> InstrumentationLibrarySpans -> Bool
$c< :: InstrumentationLibrarySpans -> InstrumentationLibrarySpans -> Bool
compare :: InstrumentationLibrarySpans
-> InstrumentationLibrarySpans -> Ordering
$ccompare :: InstrumentationLibrarySpans
-> InstrumentationLibrarySpans -> Ordering
$cp1Ord :: Eq InstrumentationLibrarySpans
Prelude.Ord)
instance Prelude.Show InstrumentationLibrarySpans where
  showsPrec :: Int -> InstrumentationLibrarySpans -> ShowS
showsPrec Int
_ InstrumentationLibrarySpans
__x String
__s
    = Char -> ShowS
Prelude.showChar
        Char
'{'
        (String -> ShowS
Prelude.showString
           (InstrumentationLibrarySpans -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort InstrumentationLibrarySpans
__x) (Char -> ShowS
Prelude.showChar Char
'}' String
__s))
instance Data.ProtoLens.Field.HasField InstrumentationLibrarySpans "instrumentationLibrary" Proto.Opentelemetry.Proto.Common.V1.Common.InstrumentationLibrary where
  fieldOf :: Proxy# "instrumentationLibrary"
-> (InstrumentationLibrary -> f InstrumentationLibrary)
-> InstrumentationLibrarySpans
-> f InstrumentationLibrarySpans
fieldOf Proxy# "instrumentationLibrary"
_
    = ((Maybe InstrumentationLibrary -> f (Maybe InstrumentationLibrary))
 -> InstrumentationLibrarySpans -> f InstrumentationLibrarySpans)
-> ((InstrumentationLibrary -> f InstrumentationLibrary)
    -> Maybe InstrumentationLibrary
    -> f (Maybe InstrumentationLibrary))
-> (InstrumentationLibrary -> f InstrumentationLibrary)
-> InstrumentationLibrarySpans
-> f InstrumentationLibrarySpans
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((InstrumentationLibrarySpans -> Maybe InstrumentationLibrary)
-> (InstrumentationLibrarySpans
    -> Maybe InstrumentationLibrary -> InstrumentationLibrarySpans)
-> Lens
     InstrumentationLibrarySpans
     InstrumentationLibrarySpans
     (Maybe InstrumentationLibrary)
     (Maybe InstrumentationLibrary)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           InstrumentationLibrarySpans -> Maybe InstrumentationLibrary
_InstrumentationLibrarySpans'instrumentationLibrary
           (\ InstrumentationLibrarySpans
x__ Maybe InstrumentationLibrary
y__
              -> InstrumentationLibrarySpans
x__
                   {_InstrumentationLibrarySpans'instrumentationLibrary :: Maybe InstrumentationLibrary
_InstrumentationLibrarySpans'instrumentationLibrary = Maybe InstrumentationLibrary
y__}))
        (InstrumentationLibrary
-> Lens' (Maybe InstrumentationLibrary) InstrumentationLibrary
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens InstrumentationLibrary
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField InstrumentationLibrarySpans "maybe'instrumentationLibrary" (Prelude.Maybe Proto.Opentelemetry.Proto.Common.V1.Common.InstrumentationLibrary) where
  fieldOf :: Proxy# "maybe'instrumentationLibrary"
-> (Maybe InstrumentationLibrary
    -> f (Maybe InstrumentationLibrary))
-> InstrumentationLibrarySpans
-> f InstrumentationLibrarySpans
fieldOf Proxy# "maybe'instrumentationLibrary"
_
    = ((Maybe InstrumentationLibrary -> f (Maybe InstrumentationLibrary))
 -> InstrumentationLibrarySpans -> f InstrumentationLibrarySpans)
-> ((Maybe InstrumentationLibrary
     -> f (Maybe InstrumentationLibrary))
    -> Maybe InstrumentationLibrary
    -> f (Maybe InstrumentationLibrary))
-> (Maybe InstrumentationLibrary
    -> f (Maybe InstrumentationLibrary))
-> InstrumentationLibrarySpans
-> f InstrumentationLibrarySpans
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((InstrumentationLibrarySpans -> Maybe InstrumentationLibrary)
-> (InstrumentationLibrarySpans
    -> Maybe InstrumentationLibrary -> InstrumentationLibrarySpans)
-> Lens
     InstrumentationLibrarySpans
     InstrumentationLibrarySpans
     (Maybe InstrumentationLibrary)
     (Maybe InstrumentationLibrary)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           InstrumentationLibrarySpans -> Maybe InstrumentationLibrary
_InstrumentationLibrarySpans'instrumentationLibrary
           (\ InstrumentationLibrarySpans
x__ Maybe InstrumentationLibrary
y__
              -> InstrumentationLibrarySpans
x__
                   {_InstrumentationLibrarySpans'instrumentationLibrary :: Maybe InstrumentationLibrary
_InstrumentationLibrarySpans'instrumentationLibrary = Maybe InstrumentationLibrary
y__}))
        (Maybe InstrumentationLibrary -> f (Maybe InstrumentationLibrary))
-> Maybe InstrumentationLibrary -> f (Maybe InstrumentationLibrary)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField InstrumentationLibrarySpans "spans" [Span] where
  fieldOf :: Proxy# "spans"
-> ([Span] -> f [Span])
-> InstrumentationLibrarySpans
-> f InstrumentationLibrarySpans
fieldOf Proxy# "spans"
_
    = ((Vector Span -> f (Vector Span))
 -> InstrumentationLibrarySpans -> f InstrumentationLibrarySpans)
-> (([Span] -> f [Span]) -> Vector Span -> f (Vector Span))
-> ([Span] -> f [Span])
-> InstrumentationLibrarySpans
-> f InstrumentationLibrarySpans
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((InstrumentationLibrarySpans -> Vector Span)
-> (InstrumentationLibrarySpans
    -> Vector Span -> InstrumentationLibrarySpans)
-> Lens
     InstrumentationLibrarySpans
     InstrumentationLibrarySpans
     (Vector Span)
     (Vector Span)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           InstrumentationLibrarySpans -> Vector Span
_InstrumentationLibrarySpans'spans
           (\ InstrumentationLibrarySpans
x__ Vector Span
y__ -> InstrumentationLibrarySpans
x__ {_InstrumentationLibrarySpans'spans :: Vector Span
_InstrumentationLibrarySpans'spans = Vector Span
y__}))
        ((Vector Span -> [Span])
-> (Vector Span -> [Span] -> Vector Span)
-> Lens (Vector Span) (Vector Span) [Span] [Span]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Vector Span -> [Span]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
           (\ Vector Span
_ [Span]
y__ -> [Span] -> Vector Span
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [Span]
y__))
instance Data.ProtoLens.Field.HasField InstrumentationLibrarySpans "vec'spans" (Data.Vector.Vector Span) where
  fieldOf :: Proxy# "vec'spans"
-> (Vector Span -> f (Vector Span))
-> InstrumentationLibrarySpans
-> f InstrumentationLibrarySpans
fieldOf Proxy# "vec'spans"
_
    = ((Vector Span -> f (Vector Span))
 -> InstrumentationLibrarySpans -> f InstrumentationLibrarySpans)
-> ((Vector Span -> f (Vector Span))
    -> Vector Span -> f (Vector Span))
-> (Vector Span -> f (Vector Span))
-> InstrumentationLibrarySpans
-> f InstrumentationLibrarySpans
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((InstrumentationLibrarySpans -> Vector Span)
-> (InstrumentationLibrarySpans
    -> Vector Span -> InstrumentationLibrarySpans)
-> Lens
     InstrumentationLibrarySpans
     InstrumentationLibrarySpans
     (Vector Span)
     (Vector Span)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           InstrumentationLibrarySpans -> Vector Span
_InstrumentationLibrarySpans'spans
           (\ InstrumentationLibrarySpans
x__ Vector Span
y__ -> InstrumentationLibrarySpans
x__ {_InstrumentationLibrarySpans'spans :: Vector Span
_InstrumentationLibrarySpans'spans = Vector Span
y__}))
        (Vector Span -> f (Vector Span)) -> Vector Span -> f (Vector Span)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField InstrumentationLibrarySpans "schemaUrl" Data.Text.Text where
  fieldOf :: Proxy# "schemaUrl"
-> (Text -> f Text)
-> InstrumentationLibrarySpans
-> f InstrumentationLibrarySpans
fieldOf Proxy# "schemaUrl"
_
    = ((Text -> f Text)
 -> InstrumentationLibrarySpans -> f InstrumentationLibrarySpans)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> InstrumentationLibrarySpans
-> f InstrumentationLibrarySpans
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((InstrumentationLibrarySpans -> Text)
-> (InstrumentationLibrarySpans
    -> Text -> InstrumentationLibrarySpans)
-> Lens
     InstrumentationLibrarySpans InstrumentationLibrarySpans Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           InstrumentationLibrarySpans -> Text
_InstrumentationLibrarySpans'schemaUrl
           (\ InstrumentationLibrarySpans
x__ Text
y__ -> InstrumentationLibrarySpans
x__ {_InstrumentationLibrarySpans'schemaUrl :: Text
_InstrumentationLibrarySpans'schemaUrl = Text
y__}))
        (Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message InstrumentationLibrarySpans where
  messageName :: Proxy InstrumentationLibrarySpans -> Text
messageName Proxy InstrumentationLibrarySpans
_
    = String -> Text
Data.Text.pack
        String
"opentelemetry.proto.trace.v1.InstrumentationLibrarySpans"
  packedMessageDescriptor :: Proxy InstrumentationLibrarySpans -> ByteString
packedMessageDescriptor Proxy InstrumentationLibrarySpans
_
    = ByteString
"\n\
      \\ESCInstrumentationLibrarySpans\DC2n\n\
      \\ETBinstrumentation_library\CAN\SOH \SOH(\v25.opentelemetry.proto.common.v1.InstrumentationLibraryR\SYNinstrumentationLibrary\DC28\n\
      \\ENQspans\CAN\STX \ETX(\v2\".opentelemetry.proto.trace.v1.SpanR\ENQspans\DC2\GS\n\
      \\n\
      \schema_url\CAN\ETX \SOH(\tR\tschemaUrl"
  packedFileDescriptor :: Proxy InstrumentationLibrarySpans -> ByteString
packedFileDescriptor Proxy InstrumentationLibrarySpans
_ = ByteString
packedFileDescriptor
  fieldsByTag :: Map Tag (FieldDescriptor InstrumentationLibrarySpans)
fieldsByTag
    = let
        instrumentationLibrary__field_descriptor :: FieldDescriptor InstrumentationLibrarySpans
instrumentationLibrary__field_descriptor
          = String
-> FieldTypeDescriptor InstrumentationLibrary
-> FieldAccessor InstrumentationLibrarySpans InstrumentationLibrary
-> FieldDescriptor InstrumentationLibrarySpans
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"instrumentation_library"
              (MessageOrGroup -> FieldTypeDescriptor InstrumentationLibrary
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
                 Data.ProtoLens.FieldTypeDescriptor Proto.Opentelemetry.Proto.Common.V1.Common.InstrumentationLibrary)
              (Lens
  InstrumentationLibrarySpans
  InstrumentationLibrarySpans
  (Maybe InstrumentationLibrary)
  (Maybe InstrumentationLibrary)
-> FieldAccessor InstrumentationLibrarySpans InstrumentationLibrary
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
                 (forall s a (f :: * -> *).
(HasField s "maybe'instrumentationLibrary" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'instrumentationLibrary")) ::
              Data.ProtoLens.FieldDescriptor InstrumentationLibrarySpans
        spans__field_descriptor :: FieldDescriptor InstrumentationLibrarySpans
spans__field_descriptor
          = String
-> FieldTypeDescriptor Span
-> FieldAccessor InstrumentationLibrarySpans Span
-> FieldDescriptor InstrumentationLibrarySpans
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"spans"
              (MessageOrGroup -> FieldTypeDescriptor Span
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
                 Data.ProtoLens.FieldTypeDescriptor Span)
              (Packing
-> Lens' InstrumentationLibrarySpans [Span]
-> FieldAccessor InstrumentationLibrarySpans Span
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
                 Packing
Data.ProtoLens.Unpacked (forall s a (f :: * -> *).
(HasField s "spans" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"spans")) ::
              Data.ProtoLens.FieldDescriptor InstrumentationLibrarySpans
        schemaUrl__field_descriptor :: FieldDescriptor InstrumentationLibrarySpans
schemaUrl__field_descriptor
          = String
-> FieldTypeDescriptor Text
-> FieldAccessor InstrumentationLibrarySpans Text
-> FieldDescriptor InstrumentationLibrarySpans
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"schema_url"
              (ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
                 Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
              (WireDefault Text
-> Lens
     InstrumentationLibrarySpans InstrumentationLibrarySpans Text Text
-> FieldAccessor InstrumentationLibrarySpans Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault Text
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional
                 (forall s a (f :: * -> *).
(HasField s "schemaUrl" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"schemaUrl")) ::
              Data.ProtoLens.FieldDescriptor InstrumentationLibrarySpans
      in
        [(Tag, FieldDescriptor InstrumentationLibrarySpans)]
-> Map Tag (FieldDescriptor InstrumentationLibrarySpans)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
          [(Int -> Tag
Data.ProtoLens.Tag Int
1, FieldDescriptor InstrumentationLibrarySpans
instrumentationLibrary__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
2, FieldDescriptor InstrumentationLibrarySpans
spans__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
3, FieldDescriptor InstrumentationLibrarySpans
schemaUrl__field_descriptor)]
  unknownFields :: LensLike' f InstrumentationLibrarySpans FieldSet
unknownFields
    = (InstrumentationLibrarySpans -> FieldSet)
-> (InstrumentationLibrarySpans
    -> FieldSet -> InstrumentationLibrarySpans)
-> Lens' InstrumentationLibrarySpans FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
        InstrumentationLibrarySpans -> FieldSet
_InstrumentationLibrarySpans'_unknownFields
        (\ InstrumentationLibrarySpans
x__ FieldSet
y__
           -> InstrumentationLibrarySpans
x__ {_InstrumentationLibrarySpans'_unknownFields :: FieldSet
_InstrumentationLibrarySpans'_unknownFields = FieldSet
y__})
  defMessage :: InstrumentationLibrarySpans
defMessage
    = InstrumentationLibrarySpans'_constructor :: Maybe InstrumentationLibrary
-> Vector Span -> Text -> FieldSet -> InstrumentationLibrarySpans
InstrumentationLibrarySpans'_constructor
        {_InstrumentationLibrarySpans'instrumentationLibrary :: Maybe InstrumentationLibrary
_InstrumentationLibrarySpans'instrumentationLibrary = Maybe InstrumentationLibrary
forall a. Maybe a
Prelude.Nothing,
         _InstrumentationLibrarySpans'spans :: Vector Span
_InstrumentationLibrarySpans'spans = Vector Span
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
         _InstrumentationLibrarySpans'schemaUrl :: Text
_InstrumentationLibrarySpans'schemaUrl = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _InstrumentationLibrarySpans'_unknownFields :: FieldSet
_InstrumentationLibrarySpans'_unknownFields = []}
  parseMessage :: Parser InstrumentationLibrarySpans
parseMessage
    = let
        loop ::
          InstrumentationLibrarySpans
          -> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld Span
             -> Data.ProtoLens.Encoding.Bytes.Parser InstrumentationLibrarySpans
        loop :: InstrumentationLibrarySpans
-> Growing Vector RealWorld Span
-> Parser InstrumentationLibrarySpans
loop InstrumentationLibrarySpans
x Growing Vector RealWorld Span
mutable'spans
          = do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
               if Bool
end then
                   do Vector Span
frozen'spans <- IO (Vector Span) -> Parser (Vector Span)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                        (Growing Vector (PrimState IO) Span -> IO (Vector Span)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze Growing Vector RealWorld Span
Growing Vector (PrimState IO) Span
mutable'spans)
                      (let missing :: [a]
missing = []
                       in
                         if [Any] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [Any]
forall a. [a]
missing then
                             () -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
                         else
                             String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
                               (String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
                                  String
"Missing required fields: "
                                  ([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
forall a. [a]
missing :: [Prelude.String]))))
                      InstrumentationLibrarySpans -> Parser InstrumentationLibrarySpans
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
                        (Setter
  InstrumentationLibrarySpans
  InstrumentationLibrarySpans
  FieldSet
  FieldSet
-> (FieldSet -> FieldSet)
-> InstrumentationLibrarySpans
-> InstrumentationLibrarySpans
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
                           forall msg. Message msg => Lens' msg FieldSet
Setter
  InstrumentationLibrarySpans
  InstrumentationLibrarySpans
  FieldSet
  FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
                           (Setter
  InstrumentationLibrarySpans
  InstrumentationLibrarySpans
  (Vector Span)
  (Vector Span)
-> Vector Span
-> InstrumentationLibrarySpans
-> InstrumentationLibrarySpans
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
                              (forall s a (f :: * -> *).
(HasField s "vec'spans" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'spans") Vector Span
frozen'spans InstrumentationLibrarySpans
x))
               else
                   do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                      case Word64
tag of
                        Word64
10
                          -> do InstrumentationLibrary
y <- Parser InstrumentationLibrary
-> String -> Parser InstrumentationLibrary
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       (do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                           Int
-> Parser InstrumentationLibrary -> Parser InstrumentationLibrary
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
                                             (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser InstrumentationLibrary
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
                                       String
"instrumentation_library"
                                InstrumentationLibrarySpans
-> Growing Vector RealWorld Span
-> Parser InstrumentationLibrarySpans
loop
                                  (Setter
  InstrumentationLibrarySpans
  InstrumentationLibrarySpans
  InstrumentationLibrary
  InstrumentationLibrary
-> InstrumentationLibrary
-> InstrumentationLibrarySpans
-> InstrumentationLibrarySpans
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
                                     (forall s a (f :: * -> *).
(HasField s "instrumentationLibrary" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"instrumentationLibrary") InstrumentationLibrary
y InstrumentationLibrarySpans
x)
                                  Growing Vector RealWorld Span
mutable'spans
                        Word64
18
                          -> do !Span
y <- Parser Span -> String -> Parser Span
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                        (do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                            Int -> Parser Span -> Parser Span
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
                                              (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
                                              Parser Span
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
                                        String
"spans"
                                Growing Vector RealWorld Span
v <- IO (Growing Vector RealWorld Span)
-> Parser (Growing Vector RealWorld Span)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                       (Growing Vector (PrimState IO) Span
-> Span -> IO (Growing Vector (PrimState IO) Span)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append Growing Vector RealWorld Span
Growing Vector (PrimState IO) Span
mutable'spans Span
y)
                                InstrumentationLibrarySpans
-> Growing Vector RealWorld Span
-> Parser InstrumentationLibrarySpans
loop InstrumentationLibrarySpans
x Growing Vector RealWorld Span
v
                        Word64
26
                          -> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       (do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                                       Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
                                                         (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
                                           Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
                                             (case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
                                                (Prelude.Left UnicodeException
err)
                                                  -> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
                                                (Prelude.Right Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
                                       String
"schema_url"
                                InstrumentationLibrarySpans
-> Growing Vector RealWorld Span
-> Parser InstrumentationLibrarySpans
loop
                                  (Setter
  InstrumentationLibrarySpans InstrumentationLibrarySpans Text Text
-> Text
-> InstrumentationLibrarySpans
-> InstrumentationLibrarySpans
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "schemaUrl" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"schemaUrl") Text
y InstrumentationLibrarySpans
x)
                                  Growing Vector RealWorld Span
mutable'spans
                        Word64
wire
                          -> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
                                        Word64
wire
                                InstrumentationLibrarySpans
-> Growing Vector RealWorld Span
-> Parser InstrumentationLibrarySpans
loop
                                  (Setter
  InstrumentationLibrarySpans
  InstrumentationLibrarySpans
  FieldSet
  FieldSet
-> (FieldSet -> FieldSet)
-> InstrumentationLibrarySpans
-> InstrumentationLibrarySpans
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
                                     forall msg. Message msg => Lens' msg FieldSet
Setter
  InstrumentationLibrarySpans
  InstrumentationLibrarySpans
  FieldSet
  FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) InstrumentationLibrarySpans
x)
                                  Growing Vector RealWorld Span
mutable'spans
      in
        Parser InstrumentationLibrarySpans
-> String -> Parser InstrumentationLibrarySpans
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
          (do Growing Vector RealWorld Span
mutable'spans <- IO (Growing Vector RealWorld Span)
-> Parser (Growing Vector RealWorld Span)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                 IO (Growing Vector RealWorld Span)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
              InstrumentationLibrarySpans
-> Growing Vector RealWorld Span
-> Parser InstrumentationLibrarySpans
loop InstrumentationLibrarySpans
forall msg. Message msg => msg
Data.ProtoLens.defMessage Growing Vector RealWorld Span
mutable'spans)
          String
"InstrumentationLibrarySpans"
  buildMessage :: InstrumentationLibrarySpans -> Builder
buildMessage
    = \ InstrumentationLibrarySpans
_x
        -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
             (case
                  FoldLike
  (Maybe InstrumentationLibrary)
  InstrumentationLibrarySpans
  InstrumentationLibrarySpans
  (Maybe InstrumentationLibrary)
  (Maybe InstrumentationLibrary)
-> InstrumentationLibrarySpans -> Maybe InstrumentationLibrary
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
                    (forall s a (f :: * -> *).
(HasField s "maybe'instrumentationLibrary" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'instrumentationLibrary") InstrumentationLibrarySpans
_x
              of
                Maybe InstrumentationLibrary
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
                (Prelude.Just InstrumentationLibrary
_v)
                  -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                       (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
10)
                       ((ByteString -> Builder)
-> (InstrumentationLibrary -> ByteString)
-> InstrumentationLibrary
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                          (\ ByteString
bs
                             -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                  (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                     (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
                                  (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
                          InstrumentationLibrary -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage InstrumentationLibrary
_v))
             (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                ((Span -> Builder) -> Vector Span -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
                   (\ Span
_v
                      -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                           (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
18)
                           ((ByteString -> Builder) -> (Span -> ByteString) -> Span -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                              (\ ByteString
bs
                                 -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                      (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                         (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
                                      (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
                              Span -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage Span
_v))
                   (FoldLike
  (Vector Span)
  InstrumentationLibrarySpans
  InstrumentationLibrarySpans
  (Vector Span)
  (Vector Span)
-> InstrumentationLibrarySpans -> Vector Span
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "vec'spans" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'spans") InstrumentationLibrarySpans
_x))
                (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                   (let
                      _v :: Text
_v = FoldLike
  Text
  InstrumentationLibrarySpans
  InstrumentationLibrarySpans
  Text
  Text
-> InstrumentationLibrarySpans -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "schemaUrl" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"schemaUrl") InstrumentationLibrarySpans
_x
                    in
                      if Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) Text
_v Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                          Builder
forall a. Monoid a => a
Data.Monoid.mempty
                      else
                          Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                            (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
26)
                            ((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                               (\ ByteString
bs
                                  -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                       (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                          (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
                                       (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
                               Text -> ByteString
Data.Text.Encoding.encodeUtf8 Text
_v))
                   (FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
                      (FoldLike
  FieldSet
  InstrumentationLibrarySpans
  InstrumentationLibrarySpans
  FieldSet
  FieldSet
-> InstrumentationLibrarySpans -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
  FieldSet
  InstrumentationLibrarySpans
  InstrumentationLibrarySpans
  FieldSet
  FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields InstrumentationLibrarySpans
_x))))
instance Control.DeepSeq.NFData InstrumentationLibrarySpans where
  rnf :: InstrumentationLibrarySpans -> ()
rnf
    = \ InstrumentationLibrarySpans
x__
        -> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
             (InstrumentationLibrarySpans -> FieldSet
_InstrumentationLibrarySpans'_unknownFields InstrumentationLibrarySpans
x__)
             (Maybe InstrumentationLibrary -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                (InstrumentationLibrarySpans -> Maybe InstrumentationLibrary
_InstrumentationLibrarySpans'instrumentationLibrary InstrumentationLibrarySpans
x__)
                (Vector Span -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                   (InstrumentationLibrarySpans -> Vector Span
_InstrumentationLibrarySpans'spans InstrumentationLibrarySpans
x__)
                   (Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                      (InstrumentationLibrarySpans -> Text
_InstrumentationLibrarySpans'schemaUrl InstrumentationLibrarySpans
x__) ())))
{- | Fields :
     
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.resource' @:: Lens' ResourceSpans Proto.Opentelemetry.Proto.Resource.V1.Resource.Resource@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.maybe'resource' @:: Lens' ResourceSpans (Prelude.Maybe Proto.Opentelemetry.Proto.Resource.V1.Resource.Resource)@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.instrumentationLibrarySpans' @:: Lens' ResourceSpans [InstrumentationLibrarySpans]@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.vec'instrumentationLibrarySpans' @:: Lens' ResourceSpans (Data.Vector.Vector InstrumentationLibrarySpans)@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.schemaUrl' @:: Lens' ResourceSpans Data.Text.Text@ -}
data ResourceSpans
  = ResourceSpans'_constructor {ResourceSpans -> Maybe Resource
_ResourceSpans'resource :: !(Prelude.Maybe Proto.Opentelemetry.Proto.Resource.V1.Resource.Resource),
                                ResourceSpans -> Vector InstrumentationLibrarySpans
_ResourceSpans'instrumentationLibrarySpans :: !(Data.Vector.Vector InstrumentationLibrarySpans),
                                ResourceSpans -> Text
_ResourceSpans'schemaUrl :: !Data.Text.Text,
                                ResourceSpans -> FieldSet
_ResourceSpans'_unknownFields :: !Data.ProtoLens.FieldSet}
  deriving stock (ResourceSpans -> ResourceSpans -> Bool
(ResourceSpans -> ResourceSpans -> Bool)
-> (ResourceSpans -> ResourceSpans -> Bool) -> Eq ResourceSpans
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResourceSpans -> ResourceSpans -> Bool
$c/= :: ResourceSpans -> ResourceSpans -> Bool
== :: ResourceSpans -> ResourceSpans -> Bool
$c== :: ResourceSpans -> ResourceSpans -> Bool
Prelude.Eq, Eq ResourceSpans
Eq ResourceSpans
-> (ResourceSpans -> ResourceSpans -> Ordering)
-> (ResourceSpans -> ResourceSpans -> Bool)
-> (ResourceSpans -> ResourceSpans -> Bool)
-> (ResourceSpans -> ResourceSpans -> Bool)
-> (ResourceSpans -> ResourceSpans -> Bool)
-> (ResourceSpans -> ResourceSpans -> ResourceSpans)
-> (ResourceSpans -> ResourceSpans -> ResourceSpans)
-> Ord ResourceSpans
ResourceSpans -> ResourceSpans -> Bool
ResourceSpans -> ResourceSpans -> Ordering
ResourceSpans -> ResourceSpans -> ResourceSpans
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 :: ResourceSpans -> ResourceSpans -> ResourceSpans
$cmin :: ResourceSpans -> ResourceSpans -> ResourceSpans
max :: ResourceSpans -> ResourceSpans -> ResourceSpans
$cmax :: ResourceSpans -> ResourceSpans -> ResourceSpans
>= :: ResourceSpans -> ResourceSpans -> Bool
$c>= :: ResourceSpans -> ResourceSpans -> Bool
> :: ResourceSpans -> ResourceSpans -> Bool
$c> :: ResourceSpans -> ResourceSpans -> Bool
<= :: ResourceSpans -> ResourceSpans -> Bool
$c<= :: ResourceSpans -> ResourceSpans -> Bool
< :: ResourceSpans -> ResourceSpans -> Bool
$c< :: ResourceSpans -> ResourceSpans -> Bool
compare :: ResourceSpans -> ResourceSpans -> Ordering
$ccompare :: ResourceSpans -> ResourceSpans -> Ordering
$cp1Ord :: Eq ResourceSpans
Prelude.Ord)
instance Prelude.Show ResourceSpans where
  showsPrec :: Int -> ResourceSpans -> ShowS
showsPrec Int
_ ResourceSpans
__x String
__s
    = Char -> ShowS
Prelude.showChar
        Char
'{'
        (String -> ShowS
Prelude.showString
           (ResourceSpans -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort ResourceSpans
__x) (Char -> ShowS
Prelude.showChar Char
'}' String
__s))
instance Data.ProtoLens.Field.HasField ResourceSpans "resource" Proto.Opentelemetry.Proto.Resource.V1.Resource.Resource where
  fieldOf :: Proxy# "resource"
-> (Resource -> f Resource) -> ResourceSpans -> f ResourceSpans
fieldOf Proxy# "resource"
_
    = ((Maybe Resource -> f (Maybe Resource))
 -> ResourceSpans -> f ResourceSpans)
-> ((Resource -> f Resource)
    -> Maybe Resource -> f (Maybe Resource))
-> (Resource -> f Resource)
-> ResourceSpans
-> f ResourceSpans
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((ResourceSpans -> Maybe Resource)
-> (ResourceSpans -> Maybe Resource -> ResourceSpans)
-> Lens
     ResourceSpans ResourceSpans (Maybe Resource) (Maybe Resource)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           ResourceSpans -> Maybe Resource
_ResourceSpans'resource
           (\ ResourceSpans
x__ Maybe Resource
y__ -> ResourceSpans
x__ {_ResourceSpans'resource :: Maybe Resource
_ResourceSpans'resource = Maybe Resource
y__}))
        (Resource -> Lens' (Maybe Resource) Resource
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Resource
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField ResourceSpans "maybe'resource" (Prelude.Maybe Proto.Opentelemetry.Proto.Resource.V1.Resource.Resource) where
  fieldOf :: Proxy# "maybe'resource"
-> (Maybe Resource -> f (Maybe Resource))
-> ResourceSpans
-> f ResourceSpans
fieldOf Proxy# "maybe'resource"
_
    = ((Maybe Resource -> f (Maybe Resource))
 -> ResourceSpans -> f ResourceSpans)
-> ((Maybe Resource -> f (Maybe Resource))
    -> Maybe Resource -> f (Maybe Resource))
-> (Maybe Resource -> f (Maybe Resource))
-> ResourceSpans
-> f ResourceSpans
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((ResourceSpans -> Maybe Resource)
-> (ResourceSpans -> Maybe Resource -> ResourceSpans)
-> Lens
     ResourceSpans ResourceSpans (Maybe Resource) (Maybe Resource)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           ResourceSpans -> Maybe Resource
_ResourceSpans'resource
           (\ ResourceSpans
x__ Maybe Resource
y__ -> ResourceSpans
x__ {_ResourceSpans'resource :: Maybe Resource
_ResourceSpans'resource = Maybe Resource
y__}))
        (Maybe Resource -> f (Maybe Resource))
-> Maybe Resource -> f (Maybe Resource)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField ResourceSpans "instrumentationLibrarySpans" [InstrumentationLibrarySpans] where
  fieldOf :: Proxy# "instrumentationLibrarySpans"
-> ([InstrumentationLibrarySpans]
    -> f [InstrumentationLibrarySpans])
-> ResourceSpans
-> f ResourceSpans
fieldOf Proxy# "instrumentationLibrarySpans"
_
    = ((Vector InstrumentationLibrarySpans
  -> f (Vector InstrumentationLibrarySpans))
 -> ResourceSpans -> f ResourceSpans)
-> (([InstrumentationLibrarySpans]
     -> f [InstrumentationLibrarySpans])
    -> Vector InstrumentationLibrarySpans
    -> f (Vector InstrumentationLibrarySpans))
-> ([InstrumentationLibrarySpans]
    -> f [InstrumentationLibrarySpans])
-> ResourceSpans
-> f ResourceSpans
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((ResourceSpans -> Vector InstrumentationLibrarySpans)
-> (ResourceSpans
    -> Vector InstrumentationLibrarySpans -> ResourceSpans)
-> Lens
     ResourceSpans
     ResourceSpans
     (Vector InstrumentationLibrarySpans)
     (Vector InstrumentationLibrarySpans)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           ResourceSpans -> Vector InstrumentationLibrarySpans
_ResourceSpans'instrumentationLibrarySpans
           (\ ResourceSpans
x__ Vector InstrumentationLibrarySpans
y__
              -> ResourceSpans
x__ {_ResourceSpans'instrumentationLibrarySpans :: Vector InstrumentationLibrarySpans
_ResourceSpans'instrumentationLibrarySpans = Vector InstrumentationLibrarySpans
y__}))
        ((Vector InstrumentationLibrarySpans
 -> [InstrumentationLibrarySpans])
-> (Vector InstrumentationLibrarySpans
    -> [InstrumentationLibrarySpans]
    -> Vector InstrumentationLibrarySpans)
-> Lens
     (Vector InstrumentationLibrarySpans)
     (Vector InstrumentationLibrarySpans)
     [InstrumentationLibrarySpans]
     [InstrumentationLibrarySpans]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Vector InstrumentationLibrarySpans -> [InstrumentationLibrarySpans]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
           (\ Vector InstrumentationLibrarySpans
_ [InstrumentationLibrarySpans]
y__ -> [InstrumentationLibrarySpans] -> Vector InstrumentationLibrarySpans
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [InstrumentationLibrarySpans]
y__))
instance Data.ProtoLens.Field.HasField ResourceSpans "vec'instrumentationLibrarySpans" (Data.Vector.Vector InstrumentationLibrarySpans) where
  fieldOf :: Proxy# "vec'instrumentationLibrarySpans"
-> (Vector InstrumentationLibrarySpans
    -> f (Vector InstrumentationLibrarySpans))
-> ResourceSpans
-> f ResourceSpans
fieldOf Proxy# "vec'instrumentationLibrarySpans"
_
    = ((Vector InstrumentationLibrarySpans
  -> f (Vector InstrumentationLibrarySpans))
 -> ResourceSpans -> f ResourceSpans)
-> ((Vector InstrumentationLibrarySpans
     -> f (Vector InstrumentationLibrarySpans))
    -> Vector InstrumentationLibrarySpans
    -> f (Vector InstrumentationLibrarySpans))
-> (Vector InstrumentationLibrarySpans
    -> f (Vector InstrumentationLibrarySpans))
-> ResourceSpans
-> f ResourceSpans
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((ResourceSpans -> Vector InstrumentationLibrarySpans)
-> (ResourceSpans
    -> Vector InstrumentationLibrarySpans -> ResourceSpans)
-> Lens
     ResourceSpans
     ResourceSpans
     (Vector InstrumentationLibrarySpans)
     (Vector InstrumentationLibrarySpans)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           ResourceSpans -> Vector InstrumentationLibrarySpans
_ResourceSpans'instrumentationLibrarySpans
           (\ ResourceSpans
x__ Vector InstrumentationLibrarySpans
y__
              -> ResourceSpans
x__ {_ResourceSpans'instrumentationLibrarySpans :: Vector InstrumentationLibrarySpans
_ResourceSpans'instrumentationLibrarySpans = Vector InstrumentationLibrarySpans
y__}))
        (Vector InstrumentationLibrarySpans
 -> f (Vector InstrumentationLibrarySpans))
-> Vector InstrumentationLibrarySpans
-> f (Vector InstrumentationLibrarySpans)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField ResourceSpans "schemaUrl" Data.Text.Text where
  fieldOf :: Proxy# "schemaUrl"
-> (Text -> f Text) -> ResourceSpans -> f ResourceSpans
fieldOf Proxy# "schemaUrl"
_
    = ((Text -> f Text) -> ResourceSpans -> f ResourceSpans)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> ResourceSpans
-> f ResourceSpans
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((ResourceSpans -> Text)
-> (ResourceSpans -> Text -> ResourceSpans)
-> Lens ResourceSpans ResourceSpans Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           ResourceSpans -> Text
_ResourceSpans'schemaUrl
           (\ ResourceSpans
x__ Text
y__ -> ResourceSpans
x__ {_ResourceSpans'schemaUrl :: Text
_ResourceSpans'schemaUrl = Text
y__}))
        (Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message ResourceSpans where
  messageName :: Proxy ResourceSpans -> Text
messageName Proxy ResourceSpans
_
    = String -> Text
Data.Text.pack String
"opentelemetry.proto.trace.v1.ResourceSpans"
  packedMessageDescriptor :: Proxy ResourceSpans -> ByteString
packedMessageDescriptor Proxy ResourceSpans
_
    = ByteString
"\n\
      \\rResourceSpans\DC2E\n\
      \\bresource\CAN\SOH \SOH(\v2).opentelemetry.proto.resource.v1.ResourceR\bresource\DC2}\n\
      \\GSinstrumentation_library_spans\CAN\STX \ETX(\v29.opentelemetry.proto.trace.v1.InstrumentationLibrarySpansR\ESCinstrumentationLibrarySpans\DC2\GS\n\
      \\n\
      \schema_url\CAN\ETX \SOH(\tR\tschemaUrl"
  packedFileDescriptor :: Proxy ResourceSpans -> ByteString
packedFileDescriptor Proxy ResourceSpans
_ = ByteString
packedFileDescriptor
  fieldsByTag :: Map Tag (FieldDescriptor ResourceSpans)
fieldsByTag
    = let
        resource__field_descriptor :: FieldDescriptor ResourceSpans
resource__field_descriptor
          = String
-> FieldTypeDescriptor Resource
-> FieldAccessor ResourceSpans Resource
-> FieldDescriptor ResourceSpans
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"resource"
              (MessageOrGroup -> FieldTypeDescriptor Resource
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
                 Data.ProtoLens.FieldTypeDescriptor Proto.Opentelemetry.Proto.Resource.V1.Resource.Resource)
              (Lens ResourceSpans ResourceSpans (Maybe Resource) (Maybe Resource)
-> FieldAccessor ResourceSpans Resource
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
                 (forall s a (f :: * -> *).
(HasField s "maybe'resource" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'resource")) ::
              Data.ProtoLens.FieldDescriptor ResourceSpans
        instrumentationLibrarySpans__field_descriptor :: FieldDescriptor ResourceSpans
instrumentationLibrarySpans__field_descriptor
          = String
-> FieldTypeDescriptor InstrumentationLibrarySpans
-> FieldAccessor ResourceSpans InstrumentationLibrarySpans
-> FieldDescriptor ResourceSpans
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"instrumentation_library_spans"
              (MessageOrGroup -> FieldTypeDescriptor InstrumentationLibrarySpans
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
                 Data.ProtoLens.FieldTypeDescriptor InstrumentationLibrarySpans)
              (Packing
-> Lens' ResourceSpans [InstrumentationLibrarySpans]
-> FieldAccessor ResourceSpans InstrumentationLibrarySpans
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
                 Packing
Data.ProtoLens.Unpacked
                 (forall s a (f :: * -> *).
(HasField s "instrumentationLibrarySpans" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"instrumentationLibrarySpans")) ::
              Data.ProtoLens.FieldDescriptor ResourceSpans
        schemaUrl__field_descriptor :: FieldDescriptor ResourceSpans
schemaUrl__field_descriptor
          = String
-> FieldTypeDescriptor Text
-> FieldAccessor ResourceSpans Text
-> FieldDescriptor ResourceSpans
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"schema_url"
              (ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
                 Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
              (WireDefault Text
-> Lens ResourceSpans ResourceSpans Text Text
-> FieldAccessor ResourceSpans Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault Text
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional
                 (forall s a (f :: * -> *).
(HasField s "schemaUrl" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"schemaUrl")) ::
              Data.ProtoLens.FieldDescriptor ResourceSpans
      in
        [(Tag, FieldDescriptor ResourceSpans)]
-> Map Tag (FieldDescriptor ResourceSpans)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
          [(Int -> Tag
Data.ProtoLens.Tag Int
1, FieldDescriptor ResourceSpans
resource__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
2, 
            FieldDescriptor ResourceSpans
instrumentationLibrarySpans__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
3, FieldDescriptor ResourceSpans
schemaUrl__field_descriptor)]
  unknownFields :: LensLike' f ResourceSpans FieldSet
unknownFields
    = (ResourceSpans -> FieldSet)
-> (ResourceSpans -> FieldSet -> ResourceSpans)
-> Lens' ResourceSpans FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
        ResourceSpans -> FieldSet
_ResourceSpans'_unknownFields
        (\ ResourceSpans
x__ FieldSet
y__ -> ResourceSpans
x__ {_ResourceSpans'_unknownFields :: FieldSet
_ResourceSpans'_unknownFields = FieldSet
y__})
  defMessage :: ResourceSpans
defMessage
    = ResourceSpans'_constructor :: Maybe Resource
-> Vector InstrumentationLibrarySpans
-> Text
-> FieldSet
-> ResourceSpans
ResourceSpans'_constructor
        {_ResourceSpans'resource :: Maybe Resource
_ResourceSpans'resource = Maybe Resource
forall a. Maybe a
Prelude.Nothing,
         _ResourceSpans'instrumentationLibrarySpans :: Vector InstrumentationLibrarySpans
_ResourceSpans'instrumentationLibrarySpans = Vector InstrumentationLibrarySpans
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
         _ResourceSpans'schemaUrl :: Text
_ResourceSpans'schemaUrl = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _ResourceSpans'_unknownFields :: FieldSet
_ResourceSpans'_unknownFields = []}
  parseMessage :: Parser ResourceSpans
parseMessage
    = let
        loop ::
          ResourceSpans
          -> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld InstrumentationLibrarySpans
             -> Data.ProtoLens.Encoding.Bytes.Parser ResourceSpans
        loop :: ResourceSpans
-> Growing Vector RealWorld InstrumentationLibrarySpans
-> Parser ResourceSpans
loop ResourceSpans
x Growing Vector RealWorld InstrumentationLibrarySpans
mutable'instrumentationLibrarySpans
          = do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
               if Bool
end then
                   do Vector InstrumentationLibrarySpans
frozen'instrumentationLibrarySpans <- IO (Vector InstrumentationLibrarySpans)
-> Parser (Vector InstrumentationLibrarySpans)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                                              (Growing Vector (PrimState IO) InstrumentationLibrarySpans
-> IO (Vector InstrumentationLibrarySpans)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
                                                                 Growing Vector RealWorld InstrumentationLibrarySpans
Growing Vector (PrimState IO) InstrumentationLibrarySpans
mutable'instrumentationLibrarySpans)
                      (let missing :: [a]
missing = []
                       in
                         if [Any] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [Any]
forall a. [a]
missing then
                             () -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
                         else
                             String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
                               (String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
                                  String
"Missing required fields: "
                                  ([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
forall a. [a]
missing :: [Prelude.String]))))
                      ResourceSpans -> Parser ResourceSpans
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
                        (Setter ResourceSpans ResourceSpans FieldSet FieldSet
-> (FieldSet -> FieldSet) -> ResourceSpans -> ResourceSpans
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
                           forall msg. Message msg => Lens' msg FieldSet
Setter ResourceSpans ResourceSpans FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
                           (Setter
  ResourceSpans
  ResourceSpans
  (Vector InstrumentationLibrarySpans)
  (Vector InstrumentationLibrarySpans)
-> Vector InstrumentationLibrarySpans
-> ResourceSpans
-> ResourceSpans
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
                              (forall s a (f :: * -> *).
(HasField s "vec'instrumentationLibrarySpans" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'instrumentationLibrarySpans")
                              Vector InstrumentationLibrarySpans
frozen'instrumentationLibrarySpans ResourceSpans
x))
               else
                   do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                      case Word64
tag of
                        Word64
10
                          -> do Resource
y <- Parser Resource -> String -> Parser Resource
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       (do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                           Int -> Parser Resource -> Parser Resource
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
                                             (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser Resource
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
                                       String
"resource"
                                ResourceSpans
-> Growing Vector RealWorld InstrumentationLibrarySpans
-> Parser ResourceSpans
loop
                                  (Setter ResourceSpans ResourceSpans Resource Resource
-> Resource -> ResourceSpans -> ResourceSpans
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "resource" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"resource") Resource
y ResourceSpans
x)
                                  Growing Vector RealWorld InstrumentationLibrarySpans
mutable'instrumentationLibrarySpans
                        Word64
18
                          -> do !InstrumentationLibrarySpans
y <- Parser InstrumentationLibrarySpans
-> String -> Parser InstrumentationLibrarySpans
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                        (do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                            Int
-> Parser InstrumentationLibrarySpans
-> Parser InstrumentationLibrarySpans
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
                                              (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
                                              Parser InstrumentationLibrarySpans
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
                                        String
"instrumentation_library_spans"
                                Growing Vector RealWorld InstrumentationLibrarySpans
v <- IO (Growing Vector RealWorld InstrumentationLibrarySpans)
-> Parser (Growing Vector RealWorld InstrumentationLibrarySpans)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                       (Growing Vector (PrimState IO) InstrumentationLibrarySpans
-> InstrumentationLibrarySpans
-> IO (Growing Vector (PrimState IO) InstrumentationLibrarySpans)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append
                                          Growing Vector RealWorld InstrumentationLibrarySpans
Growing Vector (PrimState IO) InstrumentationLibrarySpans
mutable'instrumentationLibrarySpans InstrumentationLibrarySpans
y)
                                ResourceSpans
-> Growing Vector RealWorld InstrumentationLibrarySpans
-> Parser ResourceSpans
loop ResourceSpans
x Growing Vector RealWorld InstrumentationLibrarySpans
v
                        Word64
26
                          -> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       (do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                                       Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
                                                         (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
                                           Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
                                             (case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
                                                (Prelude.Left UnicodeException
err)
                                                  -> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
                                                (Prelude.Right Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
                                       String
"schema_url"
                                ResourceSpans
-> Growing Vector RealWorld InstrumentationLibrarySpans
-> Parser ResourceSpans
loop
                                  (Setter ResourceSpans ResourceSpans Text Text
-> Text -> ResourceSpans -> ResourceSpans
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "schemaUrl" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"schemaUrl") Text
y ResourceSpans
x)
                                  Growing Vector RealWorld InstrumentationLibrarySpans
mutable'instrumentationLibrarySpans
                        Word64
wire
                          -> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
                                        Word64
wire
                                ResourceSpans
-> Growing Vector RealWorld InstrumentationLibrarySpans
-> Parser ResourceSpans
loop
                                  (Setter ResourceSpans ResourceSpans FieldSet FieldSet
-> (FieldSet -> FieldSet) -> ResourceSpans -> ResourceSpans
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
                                     forall msg. Message msg => Lens' msg FieldSet
Setter ResourceSpans ResourceSpans FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) ResourceSpans
x)
                                  Growing Vector RealWorld InstrumentationLibrarySpans
mutable'instrumentationLibrarySpans
      in
        Parser ResourceSpans -> String -> Parser ResourceSpans
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
          (do Growing Vector RealWorld InstrumentationLibrarySpans
mutable'instrumentationLibrarySpans <- IO (Growing Vector RealWorld InstrumentationLibrarySpans)
-> Parser (Growing Vector RealWorld InstrumentationLibrarySpans)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                                       IO (Growing Vector RealWorld InstrumentationLibrarySpans)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
              ResourceSpans
-> Growing Vector RealWorld InstrumentationLibrarySpans
-> Parser ResourceSpans
loop ResourceSpans
forall msg. Message msg => msg
Data.ProtoLens.defMessage Growing Vector RealWorld InstrumentationLibrarySpans
mutable'instrumentationLibrarySpans)
          String
"ResourceSpans"
  buildMessage :: ResourceSpans -> Builder
buildMessage
    = \ ResourceSpans
_x
        -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
             (case
                  FoldLike
  (Maybe Resource)
  ResourceSpans
  ResourceSpans
  (Maybe Resource)
  (Maybe Resource)
-> ResourceSpans -> Maybe Resource
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "maybe'resource" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'resource") ResourceSpans
_x
              of
                Maybe Resource
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
                (Prelude.Just Resource
_v)
                  -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                       (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
10)
                       ((ByteString -> Builder)
-> (Resource -> ByteString) -> Resource -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                          (\ ByteString
bs
                             -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                  (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                     (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
                                  (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
                          Resource -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage Resource
_v))
             (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                ((InstrumentationLibrarySpans -> Builder)
-> Vector InstrumentationLibrarySpans -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
                   (\ InstrumentationLibrarySpans
_v
                      -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                           (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
18)
                           ((ByteString -> Builder)
-> (InstrumentationLibrarySpans -> ByteString)
-> InstrumentationLibrarySpans
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                              (\ ByteString
bs
                                 -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                      (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                         (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
                                      (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
                              InstrumentationLibrarySpans -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage InstrumentationLibrarySpans
_v))
                   (FoldLike
  (Vector InstrumentationLibrarySpans)
  ResourceSpans
  ResourceSpans
  (Vector InstrumentationLibrarySpans)
  (Vector InstrumentationLibrarySpans)
-> ResourceSpans -> Vector InstrumentationLibrarySpans
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
                      (forall s a (f :: * -> *).
(HasField s "vec'instrumentationLibrarySpans" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'instrumentationLibrarySpans")
                      ResourceSpans
_x))
                (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                   (let
                      _v :: Text
_v = FoldLike Text ResourceSpans ResourceSpans Text Text
-> ResourceSpans -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "schemaUrl" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"schemaUrl") ResourceSpans
_x
                    in
                      if Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) Text
_v Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                          Builder
forall a. Monoid a => a
Data.Monoid.mempty
                      else
                          Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                            (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
26)
                            ((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                               (\ ByteString
bs
                                  -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                       (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                          (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
                                       (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
                               Text -> ByteString
Data.Text.Encoding.encodeUtf8 Text
_v))
                   (FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
                      (FoldLike FieldSet ResourceSpans ResourceSpans FieldSet FieldSet
-> ResourceSpans -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet ResourceSpans ResourceSpans FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields ResourceSpans
_x))))
instance Control.DeepSeq.NFData ResourceSpans where
  rnf :: ResourceSpans -> ()
rnf
    = \ ResourceSpans
x__
        -> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
             (ResourceSpans -> FieldSet
_ResourceSpans'_unknownFields ResourceSpans
x__)
             (Maybe Resource -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                (ResourceSpans -> Maybe Resource
_ResourceSpans'resource ResourceSpans
x__)
                (Vector InstrumentationLibrarySpans -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                   (ResourceSpans -> Vector InstrumentationLibrarySpans
_ResourceSpans'instrumentationLibrarySpans ResourceSpans
x__)
                   (Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (ResourceSpans -> Text
_ResourceSpans'schemaUrl ResourceSpans
x__) ())))
{- | Fields :
     
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.traceId' @:: Lens' Span Data.ByteString.ByteString@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.spanId' @:: Lens' Span Data.ByteString.ByteString@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.traceState' @:: Lens' Span Data.Text.Text@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.parentSpanId' @:: Lens' Span Data.ByteString.ByteString@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.name' @:: Lens' Span Data.Text.Text@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.kind' @:: Lens' Span Span'SpanKind@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.startTimeUnixNano' @:: Lens' Span Data.Word.Word64@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.endTimeUnixNano' @:: Lens' Span Data.Word.Word64@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.attributes' @:: Lens' Span [Proto.Opentelemetry.Proto.Common.V1.Common.KeyValue]@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.vec'attributes' @:: Lens' Span (Data.Vector.Vector Proto.Opentelemetry.Proto.Common.V1.Common.KeyValue)@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.droppedAttributesCount' @:: Lens' Span Data.Word.Word32@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.events' @:: Lens' Span [Span'Event]@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.vec'events' @:: Lens' Span (Data.Vector.Vector Span'Event)@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.droppedEventsCount' @:: Lens' Span Data.Word.Word32@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.links' @:: Lens' Span [Span'Link]@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.vec'links' @:: Lens' Span (Data.Vector.Vector Span'Link)@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.droppedLinksCount' @:: Lens' Span Data.Word.Word32@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.status' @:: Lens' Span Status@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.maybe'status' @:: Lens' Span (Prelude.Maybe Status)@ -}
data Span
  = Span'_constructor {Span -> ByteString
_Span'traceId :: !Data.ByteString.ByteString,
                       Span -> ByteString
_Span'spanId :: !Data.ByteString.ByteString,
                       Span -> Text
_Span'traceState :: !Data.Text.Text,
                       Span -> ByteString
_Span'parentSpanId :: !Data.ByteString.ByteString,
                       Span -> Text
_Span'name :: !Data.Text.Text,
                       Span -> Span'SpanKind
_Span'kind :: !Span'SpanKind,
                       Span -> Word64
_Span'startTimeUnixNano :: !Data.Word.Word64,
                       Span -> Word64
_Span'endTimeUnixNano :: !Data.Word.Word64,
                       Span -> Vector KeyValue
_Span'attributes :: !(Data.Vector.Vector Proto.Opentelemetry.Proto.Common.V1.Common.KeyValue),
                       Span -> Word32
_Span'droppedAttributesCount :: !Data.Word.Word32,
                       Span -> Vector Span'Event
_Span'events :: !(Data.Vector.Vector Span'Event),
                       Span -> Word32
_Span'droppedEventsCount :: !Data.Word.Word32,
                       Span -> Vector Span'Link
_Span'links :: !(Data.Vector.Vector Span'Link),
                       Span -> Word32
_Span'droppedLinksCount :: !Data.Word.Word32,
                       Span -> Maybe Status
_Span'status :: !(Prelude.Maybe Status),
                       Span -> FieldSet
_Span'_unknownFields :: !Data.ProtoLens.FieldSet}
  deriving stock (Span -> Span -> Bool
(Span -> Span -> Bool) -> (Span -> Span -> Bool) -> Eq Span
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Span -> Span -> Bool
$c/= :: Span -> Span -> Bool
== :: Span -> Span -> Bool
$c== :: Span -> Span -> Bool
Prelude.Eq, Eq Span
Eq Span
-> (Span -> Span -> Ordering)
-> (Span -> Span -> Bool)
-> (Span -> Span -> Bool)
-> (Span -> Span -> Bool)
-> (Span -> Span -> Bool)
-> (Span -> Span -> Span)
-> (Span -> Span -> Span)
-> Ord Span
Span -> Span -> Bool
Span -> Span -> Ordering
Span -> Span -> Span
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 :: Span -> Span -> Span
$cmin :: Span -> Span -> Span
max :: Span -> Span -> Span
$cmax :: Span -> Span -> Span
>= :: Span -> Span -> Bool
$c>= :: Span -> Span -> Bool
> :: Span -> Span -> Bool
$c> :: Span -> Span -> Bool
<= :: Span -> Span -> Bool
$c<= :: Span -> Span -> Bool
< :: Span -> Span -> Bool
$c< :: Span -> Span -> Bool
compare :: Span -> Span -> Ordering
$ccompare :: Span -> Span -> Ordering
$cp1Ord :: Eq Span
Prelude.Ord)
instance Prelude.Show Span where
  showsPrec :: Int -> Span -> ShowS
showsPrec Int
_ Span
__x String
__s
    = Char -> ShowS
Prelude.showChar
        Char
'{'
        (String -> ShowS
Prelude.showString
           (Span -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort Span
__x) (Char -> ShowS
Prelude.showChar Char
'}' String
__s))
instance Data.ProtoLens.Field.HasField Span "traceId" Data.ByteString.ByteString where
  fieldOf :: Proxy# "traceId" -> (ByteString -> f ByteString) -> Span -> f Span
fieldOf Proxy# "traceId"
_
    = ((ByteString -> f ByteString) -> Span -> f Span)
-> ((ByteString -> f ByteString) -> ByteString -> f ByteString)
-> (ByteString -> f ByteString)
-> Span
-> f Span
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span -> ByteString)
-> (Span -> ByteString -> Span)
-> Lens Span Span ByteString ByteString
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span -> ByteString
_Span'traceId (\ Span
x__ ByteString
y__ -> Span
x__ {_Span'traceId :: ByteString
_Span'traceId = ByteString
y__}))
        (ByteString -> f ByteString) -> ByteString -> f ByteString
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Span "spanId" Data.ByteString.ByteString where
  fieldOf :: Proxy# "spanId" -> (ByteString -> f ByteString) -> Span -> f Span
fieldOf Proxy# "spanId"
_
    = ((ByteString -> f ByteString) -> Span -> f Span)
-> ((ByteString -> f ByteString) -> ByteString -> f ByteString)
-> (ByteString -> f ByteString)
-> Span
-> f Span
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span -> ByteString)
-> (Span -> ByteString -> Span)
-> Lens Span Span ByteString ByteString
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span -> ByteString
_Span'spanId (\ Span
x__ ByteString
y__ -> Span
x__ {_Span'spanId :: ByteString
_Span'spanId = ByteString
y__}))
        (ByteString -> f ByteString) -> ByteString -> f ByteString
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Span "traceState" Data.Text.Text where
  fieldOf :: Proxy# "traceState" -> (Text -> f Text) -> Span -> f Span
fieldOf Proxy# "traceState"
_
    = ((Text -> f Text) -> Span -> f Span)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> Span
-> f Span
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span -> Text)
-> (Span -> Text -> Span) -> Lens Span Span Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span -> Text
_Span'traceState (\ Span
x__ Text
y__ -> Span
x__ {_Span'traceState :: Text
_Span'traceState = Text
y__}))
        (Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Span "parentSpanId" Data.ByteString.ByteString where
  fieldOf :: Proxy# "parentSpanId"
-> (ByteString -> f ByteString) -> Span -> f Span
fieldOf Proxy# "parentSpanId"
_
    = ((ByteString -> f ByteString) -> Span -> f Span)
-> ((ByteString -> f ByteString) -> ByteString -> f ByteString)
-> (ByteString -> f ByteString)
-> Span
-> f Span
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span -> ByteString)
-> (Span -> ByteString -> Span)
-> Lens Span Span ByteString ByteString
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span -> ByteString
_Span'parentSpanId (\ Span
x__ ByteString
y__ -> Span
x__ {_Span'parentSpanId :: ByteString
_Span'parentSpanId = ByteString
y__}))
        (ByteString -> f ByteString) -> ByteString -> f ByteString
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Span "name" Data.Text.Text where
  fieldOf :: Proxy# "name" -> (Text -> f Text) -> Span -> f Span
fieldOf Proxy# "name"
_
    = ((Text -> f Text) -> Span -> f Span)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> Span
-> f Span
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span -> Text)
-> (Span -> Text -> Span) -> Lens Span Span Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span -> Text
_Span'name (\ Span
x__ Text
y__ -> Span
x__ {_Span'name :: Text
_Span'name = Text
y__}))
        (Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Span "kind" Span'SpanKind where
  fieldOf :: Proxy# "kind"
-> (Span'SpanKind -> f Span'SpanKind) -> Span -> f Span
fieldOf Proxy# "kind"
_
    = ((Span'SpanKind -> f Span'SpanKind) -> Span -> f Span)
-> ((Span'SpanKind -> f Span'SpanKind)
    -> Span'SpanKind -> f Span'SpanKind)
-> (Span'SpanKind -> f Span'SpanKind)
-> Span
-> f Span
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span -> Span'SpanKind)
-> (Span -> Span'SpanKind -> Span)
-> Lens Span Span Span'SpanKind Span'SpanKind
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span -> Span'SpanKind
_Span'kind (\ Span
x__ Span'SpanKind
y__ -> Span
x__ {_Span'kind :: Span'SpanKind
_Span'kind = Span'SpanKind
y__}))
        (Span'SpanKind -> f Span'SpanKind)
-> Span'SpanKind -> f Span'SpanKind
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Span "startTimeUnixNano" Data.Word.Word64 where
  fieldOf :: Proxy# "startTimeUnixNano"
-> (Word64 -> f Word64) -> Span -> f Span
fieldOf Proxy# "startTimeUnixNano"
_
    = ((Word64 -> f Word64) -> Span -> f Span)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> Span
-> f Span
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span -> Word64)
-> (Span -> Word64 -> Span) -> Lens Span Span Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span -> Word64
_Span'startTimeUnixNano
           (\ Span
x__ Word64
y__ -> Span
x__ {_Span'startTimeUnixNano :: Word64
_Span'startTimeUnixNano = Word64
y__}))
        (Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Span "endTimeUnixNano" Data.Word.Word64 where
  fieldOf :: Proxy# "endTimeUnixNano" -> (Word64 -> f Word64) -> Span -> f Span
fieldOf Proxy# "endTimeUnixNano"
_
    = ((Word64 -> f Word64) -> Span -> f Span)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> Span
-> f Span
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span -> Word64)
-> (Span -> Word64 -> Span) -> Lens Span Span Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span -> Word64
_Span'endTimeUnixNano
           (\ Span
x__ Word64
y__ -> Span
x__ {_Span'endTimeUnixNano :: Word64
_Span'endTimeUnixNano = Word64
y__}))
        (Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Span "attributes" [Proto.Opentelemetry.Proto.Common.V1.Common.KeyValue] where
  fieldOf :: Proxy# "attributes"
-> ([KeyValue] -> f [KeyValue]) -> Span -> f Span
fieldOf Proxy# "attributes"
_
    = ((Vector KeyValue -> f (Vector KeyValue)) -> Span -> f Span)
-> (([KeyValue] -> f [KeyValue])
    -> Vector KeyValue -> f (Vector KeyValue))
-> ([KeyValue] -> f [KeyValue])
-> Span
-> f Span
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span -> Vector KeyValue)
-> (Span -> Vector KeyValue -> Span)
-> Lens Span Span (Vector KeyValue) (Vector KeyValue)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span -> Vector KeyValue
_Span'attributes (\ Span
x__ Vector KeyValue
y__ -> Span
x__ {_Span'attributes :: Vector KeyValue
_Span'attributes = Vector KeyValue
y__}))
        ((Vector KeyValue -> [KeyValue])
-> (Vector KeyValue -> [KeyValue] -> Vector KeyValue)
-> Lens (Vector KeyValue) (Vector KeyValue) [KeyValue] [KeyValue]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Vector KeyValue -> [KeyValue]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
           (\ Vector KeyValue
_ [KeyValue]
y__ -> [KeyValue] -> Vector KeyValue
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [KeyValue]
y__))
instance Data.ProtoLens.Field.HasField Span "vec'attributes" (Data.Vector.Vector Proto.Opentelemetry.Proto.Common.V1.Common.KeyValue) where
  fieldOf :: Proxy# "vec'attributes"
-> (Vector KeyValue -> f (Vector KeyValue)) -> Span -> f Span
fieldOf Proxy# "vec'attributes"
_
    = ((Vector KeyValue -> f (Vector KeyValue)) -> Span -> f Span)
-> ((Vector KeyValue -> f (Vector KeyValue))
    -> Vector KeyValue -> f (Vector KeyValue))
-> (Vector KeyValue -> f (Vector KeyValue))
-> Span
-> f Span
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span -> Vector KeyValue)
-> (Span -> Vector KeyValue -> Span)
-> Lens Span Span (Vector KeyValue) (Vector KeyValue)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span -> Vector KeyValue
_Span'attributes (\ Span
x__ Vector KeyValue
y__ -> Span
x__ {_Span'attributes :: Vector KeyValue
_Span'attributes = Vector KeyValue
y__}))
        (Vector KeyValue -> f (Vector KeyValue))
-> Vector KeyValue -> f (Vector KeyValue)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Span "droppedAttributesCount" Data.Word.Word32 where
  fieldOf :: Proxy# "droppedAttributesCount"
-> (Word32 -> f Word32) -> Span -> f Span
fieldOf Proxy# "droppedAttributesCount"
_
    = ((Word32 -> f Word32) -> Span -> f Span)
-> ((Word32 -> f Word32) -> Word32 -> f Word32)
-> (Word32 -> f Word32)
-> Span
-> f Span
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span -> Word32)
-> (Span -> Word32 -> Span) -> Lens Span Span Word32 Word32
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span -> Word32
_Span'droppedAttributesCount
           (\ Span
x__ Word32
y__ -> Span
x__ {_Span'droppedAttributesCount :: Word32
_Span'droppedAttributesCount = Word32
y__}))
        (Word32 -> f Word32) -> Word32 -> f Word32
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Span "events" [Span'Event] where
  fieldOf :: Proxy# "events"
-> ([Span'Event] -> f [Span'Event]) -> Span -> f Span
fieldOf Proxy# "events"
_
    = ((Vector Span'Event -> f (Vector Span'Event)) -> Span -> f Span)
-> (([Span'Event] -> f [Span'Event])
    -> Vector Span'Event -> f (Vector Span'Event))
-> ([Span'Event] -> f [Span'Event])
-> Span
-> f Span
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span -> Vector Span'Event)
-> (Span -> Vector Span'Event -> Span)
-> Lens Span Span (Vector Span'Event) (Vector Span'Event)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span -> Vector Span'Event
_Span'events (\ Span
x__ Vector Span'Event
y__ -> Span
x__ {_Span'events :: Vector Span'Event
_Span'events = Vector Span'Event
y__}))
        ((Vector Span'Event -> [Span'Event])
-> (Vector Span'Event -> [Span'Event] -> Vector Span'Event)
-> Lens
     (Vector Span'Event) (Vector Span'Event) [Span'Event] [Span'Event]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Vector Span'Event -> [Span'Event]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
           (\ Vector Span'Event
_ [Span'Event]
y__ -> [Span'Event] -> Vector Span'Event
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [Span'Event]
y__))
instance Data.ProtoLens.Field.HasField Span "vec'events" (Data.Vector.Vector Span'Event) where
  fieldOf :: Proxy# "vec'events"
-> (Vector Span'Event -> f (Vector Span'Event)) -> Span -> f Span
fieldOf Proxy# "vec'events"
_
    = ((Vector Span'Event -> f (Vector Span'Event)) -> Span -> f Span)
-> ((Vector Span'Event -> f (Vector Span'Event))
    -> Vector Span'Event -> f (Vector Span'Event))
-> (Vector Span'Event -> f (Vector Span'Event))
-> Span
-> f Span
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span -> Vector Span'Event)
-> (Span -> Vector Span'Event -> Span)
-> Lens Span Span (Vector Span'Event) (Vector Span'Event)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span -> Vector Span'Event
_Span'events (\ Span
x__ Vector Span'Event
y__ -> Span
x__ {_Span'events :: Vector Span'Event
_Span'events = Vector Span'Event
y__}))
        (Vector Span'Event -> f (Vector Span'Event))
-> Vector Span'Event -> f (Vector Span'Event)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Span "droppedEventsCount" Data.Word.Word32 where
  fieldOf :: Proxy# "droppedEventsCount"
-> (Word32 -> f Word32) -> Span -> f Span
fieldOf Proxy# "droppedEventsCount"
_
    = ((Word32 -> f Word32) -> Span -> f Span)
-> ((Word32 -> f Word32) -> Word32 -> f Word32)
-> (Word32 -> f Word32)
-> Span
-> f Span
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span -> Word32)
-> (Span -> Word32 -> Span) -> Lens Span Span Word32 Word32
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span -> Word32
_Span'droppedEventsCount
           (\ Span
x__ Word32
y__ -> Span
x__ {_Span'droppedEventsCount :: Word32
_Span'droppedEventsCount = Word32
y__}))
        (Word32 -> f Word32) -> Word32 -> f Word32
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Span "links" [Span'Link] where
  fieldOf :: Proxy# "links" -> ([Span'Link] -> f [Span'Link]) -> Span -> f Span
fieldOf Proxy# "links"
_
    = ((Vector Span'Link -> f (Vector Span'Link)) -> Span -> f Span)
-> (([Span'Link] -> f [Span'Link])
    -> Vector Span'Link -> f (Vector Span'Link))
-> ([Span'Link] -> f [Span'Link])
-> Span
-> f Span
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span -> Vector Span'Link)
-> (Span -> Vector Span'Link -> Span)
-> Lens Span Span (Vector Span'Link) (Vector Span'Link)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span -> Vector Span'Link
_Span'links (\ Span
x__ Vector Span'Link
y__ -> Span
x__ {_Span'links :: Vector Span'Link
_Span'links = Vector Span'Link
y__}))
        ((Vector Span'Link -> [Span'Link])
-> (Vector Span'Link -> [Span'Link] -> Vector Span'Link)
-> Lens
     (Vector Span'Link) (Vector Span'Link) [Span'Link] [Span'Link]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Vector Span'Link -> [Span'Link]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
           (\ Vector Span'Link
_ [Span'Link]
y__ -> [Span'Link] -> Vector Span'Link
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [Span'Link]
y__))
instance Data.ProtoLens.Field.HasField Span "vec'links" (Data.Vector.Vector Span'Link) where
  fieldOf :: Proxy# "vec'links"
-> (Vector Span'Link -> f (Vector Span'Link)) -> Span -> f Span
fieldOf Proxy# "vec'links"
_
    = ((Vector Span'Link -> f (Vector Span'Link)) -> Span -> f Span)
-> ((Vector Span'Link -> f (Vector Span'Link))
    -> Vector Span'Link -> f (Vector Span'Link))
-> (Vector Span'Link -> f (Vector Span'Link))
-> Span
-> f Span
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span -> Vector Span'Link)
-> (Span -> Vector Span'Link -> Span)
-> Lens Span Span (Vector Span'Link) (Vector Span'Link)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span -> Vector Span'Link
_Span'links (\ Span
x__ Vector Span'Link
y__ -> Span
x__ {_Span'links :: Vector Span'Link
_Span'links = Vector Span'Link
y__}))
        (Vector Span'Link -> f (Vector Span'Link))
-> Vector Span'Link -> f (Vector Span'Link)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Span "droppedLinksCount" Data.Word.Word32 where
  fieldOf :: Proxy# "droppedLinksCount"
-> (Word32 -> f Word32) -> Span -> f Span
fieldOf Proxy# "droppedLinksCount"
_
    = ((Word32 -> f Word32) -> Span -> f Span)
-> ((Word32 -> f Word32) -> Word32 -> f Word32)
-> (Word32 -> f Word32)
-> Span
-> f Span
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span -> Word32)
-> (Span -> Word32 -> Span) -> Lens Span Span Word32 Word32
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span -> Word32
_Span'droppedLinksCount
           (\ Span
x__ Word32
y__ -> Span
x__ {_Span'droppedLinksCount :: Word32
_Span'droppedLinksCount = Word32
y__}))
        (Word32 -> f Word32) -> Word32 -> f Word32
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Span "status" Status where
  fieldOf :: Proxy# "status" -> (Status -> f Status) -> Span -> f Span
fieldOf Proxy# "status"
_
    = ((Maybe Status -> f (Maybe Status)) -> Span -> f Span)
-> ((Status -> f Status) -> Maybe Status -> f (Maybe Status))
-> (Status -> f Status)
-> Span
-> f Span
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span -> Maybe Status)
-> (Span -> Maybe Status -> Span)
-> Lens Span Span (Maybe Status) (Maybe Status)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span -> Maybe Status
_Span'status (\ Span
x__ Maybe Status
y__ -> Span
x__ {_Span'status :: Maybe Status
_Span'status = Maybe Status
y__}))
        (Status -> Lens' (Maybe Status) Status
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Status
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField Span "maybe'status" (Prelude.Maybe Status) where
  fieldOf :: Proxy# "maybe'status"
-> (Maybe Status -> f (Maybe Status)) -> Span -> f Span
fieldOf Proxy# "maybe'status"
_
    = ((Maybe Status -> f (Maybe Status)) -> Span -> f Span)
-> ((Maybe Status -> f (Maybe Status))
    -> Maybe Status -> f (Maybe Status))
-> (Maybe Status -> f (Maybe Status))
-> Span
-> f Span
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span -> Maybe Status)
-> (Span -> Maybe Status -> Span)
-> Lens Span Span (Maybe Status) (Maybe Status)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span -> Maybe Status
_Span'status (\ Span
x__ Maybe Status
y__ -> Span
x__ {_Span'status :: Maybe Status
_Span'status = Maybe Status
y__}))
        (Maybe Status -> f (Maybe Status))
-> Maybe Status -> f (Maybe Status)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message Span where
  messageName :: Proxy Span -> Text
messageName Proxy Span
_ = String -> Text
Data.Text.pack String
"opentelemetry.proto.trace.v1.Span"
  packedMessageDescriptor :: Proxy Span -> ByteString
packedMessageDescriptor Proxy Span
_
    = ByteString
"\n\
      \\EOTSpan\DC2\EM\n\
      \\btrace_id\CAN\SOH \SOH(\fR\atraceId\DC2\ETB\n\
      \\aspan_id\CAN\STX \SOH(\fR\ACKspanId\DC2\US\n\
      \\vtrace_state\CAN\ETX \SOH(\tR\n\
      \traceState\DC2$\n\
      \\SOparent_span_id\CAN\EOT \SOH(\fR\fparentSpanId\DC2\DC2\n\
      \\EOTname\CAN\ENQ \SOH(\tR\EOTname\DC2?\n\
      \\EOTkind\CAN\ACK \SOH(\SO2+.opentelemetry.proto.trace.v1.Span.SpanKindR\EOTkind\DC2/\n\
      \\DC4start_time_unix_nano\CAN\a \SOH(\ACKR\DC1startTimeUnixNano\DC2+\n\
      \\DC2end_time_unix_nano\CAN\b \SOH(\ACKR\SIendTimeUnixNano\DC2G\n\
      \\n\
      \attributes\CAN\t \ETX(\v2'.opentelemetry.proto.common.v1.KeyValueR\n\
      \attributes\DC28\n\
      \\CANdropped_attributes_count\CAN\n\
      \ \SOH(\rR\SYNdroppedAttributesCount\DC2@\n\
      \\ACKevents\CAN\v \ETX(\v2(.opentelemetry.proto.trace.v1.Span.EventR\ACKevents\DC20\n\
      \\DC4dropped_events_count\CAN\f \SOH(\rR\DC2droppedEventsCount\DC2=\n\
      \\ENQlinks\CAN\r \ETX(\v2'.opentelemetry.proto.trace.v1.Span.LinkR\ENQlinks\DC2.\n\
      \\DC3dropped_links_count\CAN\SO \SOH(\rR\DC1droppedLinksCount\DC2<\n\
      \\ACKstatus\CAN\SI \SOH(\v2$.opentelemetry.proto.trace.v1.StatusR\ACKstatus\SUB\196\SOH\n\
      \\ENQEvent\DC2$\n\
      \\SOtime_unix_nano\CAN\SOH \SOH(\ACKR\ftimeUnixNano\DC2\DC2\n\
      \\EOTname\CAN\STX \SOH(\tR\EOTname\DC2G\n\
      \\n\
      \attributes\CAN\ETX \ETX(\v2'.opentelemetry.proto.common.v1.KeyValueR\n\
      \attributes\DC28\n\
      \\CANdropped_attributes_count\CAN\EOT \SOH(\rR\SYNdroppedAttributesCount\SUB\222\SOH\n\
      \\EOTLink\DC2\EM\n\
      \\btrace_id\CAN\SOH \SOH(\fR\atraceId\DC2\ETB\n\
      \\aspan_id\CAN\STX \SOH(\fR\ACKspanId\DC2\US\n\
      \\vtrace_state\CAN\ETX \SOH(\tR\n\
      \traceState\DC2G\n\
      \\n\
      \attributes\CAN\EOT \ETX(\v2'.opentelemetry.proto.common.v1.KeyValueR\n\
      \attributes\DC28\n\
      \\CANdropped_attributes_count\CAN\ENQ \SOH(\rR\SYNdroppedAttributesCount\"\153\SOH\n\
      \\bSpanKind\DC2\EM\n\
      \\NAKSPAN_KIND_UNSPECIFIED\DLE\NUL\DC2\SYN\n\
      \\DC2SPAN_KIND_INTERNAL\DLE\SOH\DC2\DC4\n\
      \\DLESPAN_KIND_SERVER\DLE\STX\DC2\DC4\n\
      \\DLESPAN_KIND_CLIENT\DLE\ETX\DC2\SYN\n\
      \\DC2SPAN_KIND_PRODUCER\DLE\EOT\DC2\SYN\n\
      \\DC2SPAN_KIND_CONSUMER\DLE\ENQ"
  packedFileDescriptor :: Proxy Span -> ByteString
packedFileDescriptor Proxy Span
_ = ByteString
packedFileDescriptor
  fieldsByTag :: Map Tag (FieldDescriptor Span)
fieldsByTag
    = let
        traceId__field_descriptor :: FieldDescriptor Span
traceId__field_descriptor
          = String
-> FieldTypeDescriptor ByteString
-> FieldAccessor Span ByteString
-> FieldDescriptor Span
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"trace_id"
              (ScalarField ByteString -> FieldTypeDescriptor ByteString
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ByteString
Data.ProtoLens.BytesField ::
                 Data.ProtoLens.FieldTypeDescriptor Data.ByteString.ByteString)
              (WireDefault ByteString
-> Lens Span Span ByteString ByteString
-> FieldAccessor Span ByteString
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault ByteString
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional (forall s a (f :: * -> *).
(HasField s "traceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"traceId")) ::
              Data.ProtoLens.FieldDescriptor Span
        spanId__field_descriptor :: FieldDescriptor Span
spanId__field_descriptor
          = String
-> FieldTypeDescriptor ByteString
-> FieldAccessor Span ByteString
-> FieldDescriptor Span
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"span_id"
              (ScalarField ByteString -> FieldTypeDescriptor ByteString
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ByteString
Data.ProtoLens.BytesField ::
                 Data.ProtoLens.FieldTypeDescriptor Data.ByteString.ByteString)
              (WireDefault ByteString
-> Lens Span Span ByteString ByteString
-> FieldAccessor Span ByteString
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault ByteString
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional (forall s a (f :: * -> *).
(HasField s "spanId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"spanId")) ::
              Data.ProtoLens.FieldDescriptor Span
        traceState__field_descriptor :: FieldDescriptor Span
traceState__field_descriptor
          = String
-> FieldTypeDescriptor Text
-> FieldAccessor Span Text
-> FieldDescriptor Span
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"trace_state"
              (ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
                 Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
              (WireDefault Text
-> Lens Span Span Text Text -> FieldAccessor Span Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault Text
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional
                 (forall s a (f :: * -> *).
(HasField s "traceState" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"traceState")) ::
              Data.ProtoLens.FieldDescriptor Span
        parentSpanId__field_descriptor :: FieldDescriptor Span
parentSpanId__field_descriptor
          = String
-> FieldTypeDescriptor ByteString
-> FieldAccessor Span ByteString
-> FieldDescriptor Span
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"parent_span_id"
              (ScalarField ByteString -> FieldTypeDescriptor ByteString
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ByteString
Data.ProtoLens.BytesField ::
                 Data.ProtoLens.FieldTypeDescriptor Data.ByteString.ByteString)
              (WireDefault ByteString
-> Lens Span Span ByteString ByteString
-> FieldAccessor Span ByteString
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault ByteString
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional
                 (forall s a (f :: * -> *).
(HasField s "parentSpanId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"parentSpanId")) ::
              Data.ProtoLens.FieldDescriptor Span
        name__field_descriptor :: FieldDescriptor Span
name__field_descriptor
          = String
-> FieldTypeDescriptor Text
-> FieldAccessor Span Text
-> FieldDescriptor Span
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"name"
              (ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
                 Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
              (WireDefault Text
-> Lens Span Span Text Text -> FieldAccessor Span Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault Text
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional (forall s a (f :: * -> *).
(HasField s "name" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"name")) ::
              Data.ProtoLens.FieldDescriptor Span
        kind__field_descriptor :: FieldDescriptor Span
kind__field_descriptor
          = String
-> FieldTypeDescriptor Span'SpanKind
-> FieldAccessor Span Span'SpanKind
-> FieldDescriptor Span
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"kind"
              (ScalarField Span'SpanKind -> FieldTypeDescriptor Span'SpanKind
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Span'SpanKind
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
                 Data.ProtoLens.FieldTypeDescriptor Span'SpanKind)
              (WireDefault Span'SpanKind
-> Lens Span Span Span'SpanKind Span'SpanKind
-> FieldAccessor Span Span'SpanKind
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault Span'SpanKind
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional (forall s a (f :: * -> *).
(HasField s "kind" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"kind")) ::
              Data.ProtoLens.FieldDescriptor Span
        startTimeUnixNano__field_descriptor :: FieldDescriptor Span
startTimeUnixNano__field_descriptor
          = String
-> FieldTypeDescriptor Word64
-> FieldAccessor Span Word64
-> FieldDescriptor Span
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"start_time_unix_nano"
              (ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.Fixed64Field ::
                 Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
              (WireDefault Word64
-> Lens Span Span Word64 Word64 -> FieldAccessor Span Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault Word64
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional
                 (forall s a (f :: * -> *).
(HasField s "startTimeUnixNano" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"startTimeUnixNano")) ::
              Data.ProtoLens.FieldDescriptor Span
        endTimeUnixNano__field_descriptor :: FieldDescriptor Span
endTimeUnixNano__field_descriptor
          = String
-> FieldTypeDescriptor Word64
-> FieldAccessor Span Word64
-> FieldDescriptor Span
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"end_time_unix_nano"
              (ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.Fixed64Field ::
                 Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
              (WireDefault Word64
-> Lens Span Span Word64 Word64 -> FieldAccessor Span Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault Word64
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional
                 (forall s a (f :: * -> *).
(HasField s "endTimeUnixNano" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"endTimeUnixNano")) ::
              Data.ProtoLens.FieldDescriptor Span
        attributes__field_descriptor :: FieldDescriptor Span
attributes__field_descriptor
          = String
-> FieldTypeDescriptor KeyValue
-> FieldAccessor Span KeyValue
-> FieldDescriptor Span
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"attributes"
              (MessageOrGroup -> FieldTypeDescriptor KeyValue
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
                 Data.ProtoLens.FieldTypeDescriptor Proto.Opentelemetry.Proto.Common.V1.Common.KeyValue)
              (Packing -> Lens' Span [KeyValue] -> FieldAccessor Span KeyValue
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
                 Packing
Data.ProtoLens.Unpacked
                 (forall s a (f :: * -> *).
(HasField s "attributes" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"attributes")) ::
              Data.ProtoLens.FieldDescriptor Span
        droppedAttributesCount__field_descriptor :: FieldDescriptor Span
droppedAttributesCount__field_descriptor
          = String
-> FieldTypeDescriptor Word32
-> FieldAccessor Span Word32
-> FieldDescriptor Span
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"dropped_attributes_count"
              (ScalarField Word32 -> FieldTypeDescriptor Word32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word32
Data.ProtoLens.UInt32Field ::
                 Data.ProtoLens.FieldTypeDescriptor Data.Word.Word32)
              (WireDefault Word32
-> Lens Span Span Word32 Word32 -> FieldAccessor Span Word32
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault Word32
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional
                 (forall s a (f :: * -> *).
(HasField s "droppedAttributesCount" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"droppedAttributesCount")) ::
              Data.ProtoLens.FieldDescriptor Span
        events__field_descriptor :: FieldDescriptor Span
events__field_descriptor
          = String
-> FieldTypeDescriptor Span'Event
-> FieldAccessor Span Span'Event
-> FieldDescriptor Span
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"events"
              (MessageOrGroup -> FieldTypeDescriptor Span'Event
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
                 Data.ProtoLens.FieldTypeDescriptor Span'Event)
              (Packing -> Lens' Span [Span'Event] -> FieldAccessor Span Span'Event
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
                 Packing
Data.ProtoLens.Unpacked (forall s a (f :: * -> *).
(HasField s "events" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"events")) ::
              Data.ProtoLens.FieldDescriptor Span
        droppedEventsCount__field_descriptor :: FieldDescriptor Span
droppedEventsCount__field_descriptor
          = String
-> FieldTypeDescriptor Word32
-> FieldAccessor Span Word32
-> FieldDescriptor Span
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"dropped_events_count"
              (ScalarField Word32 -> FieldTypeDescriptor Word32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word32
Data.ProtoLens.UInt32Field ::
                 Data.ProtoLens.FieldTypeDescriptor Data.Word.Word32)
              (WireDefault Word32
-> Lens Span Span Word32 Word32 -> FieldAccessor Span Word32
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault Word32
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional
                 (forall s a (f :: * -> *).
(HasField s "droppedEventsCount" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"droppedEventsCount")) ::
              Data.ProtoLens.FieldDescriptor Span
        links__field_descriptor :: FieldDescriptor Span
links__field_descriptor
          = String
-> FieldTypeDescriptor Span'Link
-> FieldAccessor Span Span'Link
-> FieldDescriptor Span
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"links"
              (MessageOrGroup -> FieldTypeDescriptor Span'Link
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
                 Data.ProtoLens.FieldTypeDescriptor Span'Link)
              (Packing -> Lens' Span [Span'Link] -> FieldAccessor Span Span'Link
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
                 Packing
Data.ProtoLens.Unpacked (forall s a (f :: * -> *).
(HasField s "links" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"links")) ::
              Data.ProtoLens.FieldDescriptor Span
        droppedLinksCount__field_descriptor :: FieldDescriptor Span
droppedLinksCount__field_descriptor
          = String
-> FieldTypeDescriptor Word32
-> FieldAccessor Span Word32
-> FieldDescriptor Span
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"dropped_links_count"
              (ScalarField Word32 -> FieldTypeDescriptor Word32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word32
Data.ProtoLens.UInt32Field ::
                 Data.ProtoLens.FieldTypeDescriptor Data.Word.Word32)
              (WireDefault Word32
-> Lens Span Span Word32 Word32 -> FieldAccessor Span Word32
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault Word32
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional
                 (forall s a (f :: * -> *).
(HasField s "droppedLinksCount" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"droppedLinksCount")) ::
              Data.ProtoLens.FieldDescriptor Span
        status__field_descriptor :: FieldDescriptor Span
status__field_descriptor
          = String
-> FieldTypeDescriptor Status
-> FieldAccessor Span Status
-> FieldDescriptor Span
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"status"
              (MessageOrGroup -> FieldTypeDescriptor Status
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
                 Data.ProtoLens.FieldTypeDescriptor Status)
              (Lens Span Span (Maybe Status) (Maybe Status)
-> FieldAccessor Span Status
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
                 (forall s a (f :: * -> *).
(HasField s "maybe'status" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'status")) ::
              Data.ProtoLens.FieldDescriptor Span
      in
        [(Tag, FieldDescriptor Span)] -> Map Tag (FieldDescriptor Span)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
          [(Int -> Tag
Data.ProtoLens.Tag Int
1, FieldDescriptor Span
traceId__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
2, FieldDescriptor Span
spanId__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
3, FieldDescriptor Span
traceState__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
4, FieldDescriptor Span
parentSpanId__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
5, FieldDescriptor Span
name__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
6, FieldDescriptor Span
kind__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
7, FieldDescriptor Span
startTimeUnixNano__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
8, FieldDescriptor Span
endTimeUnixNano__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
9, FieldDescriptor Span
attributes__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
10, FieldDescriptor Span
droppedAttributesCount__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
11, FieldDescriptor Span
events__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
12, FieldDescriptor Span
droppedEventsCount__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
13, FieldDescriptor Span
links__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
14, FieldDescriptor Span
droppedLinksCount__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
15, FieldDescriptor Span
status__field_descriptor)]
  unknownFields :: LensLike' f Span FieldSet
unknownFields
    = (Span -> FieldSet)
-> (Span -> FieldSet -> Span) -> Lens' Span FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
        Span -> FieldSet
_Span'_unknownFields
        (\ Span
x__ FieldSet
y__ -> Span
x__ {_Span'_unknownFields :: FieldSet
_Span'_unknownFields = FieldSet
y__})
  defMessage :: Span
defMessage
    = Span'_constructor :: ByteString
-> ByteString
-> Text
-> ByteString
-> Text
-> Span'SpanKind
-> Word64
-> Word64
-> Vector KeyValue
-> Word32
-> Vector Span'Event
-> Word32
-> Vector Span'Link
-> Word32
-> Maybe Status
-> FieldSet
-> Span
Span'_constructor
        {_Span'traceId :: ByteString
_Span'traceId = ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _Span'spanId :: ByteString
_Span'spanId = ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _Span'traceState :: Text
_Span'traceState = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _Span'parentSpanId :: ByteString
_Span'parentSpanId = ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _Span'name :: Text
_Span'name = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _Span'kind :: Span'SpanKind
_Span'kind = Span'SpanKind
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _Span'startTimeUnixNano :: Word64
_Span'startTimeUnixNano = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _Span'endTimeUnixNano :: Word64
_Span'endTimeUnixNano = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _Span'attributes :: Vector KeyValue
_Span'attributes = Vector KeyValue
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
         _Span'droppedAttributesCount :: Word32
_Span'droppedAttributesCount = Word32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _Span'events :: Vector Span'Event
_Span'events = Vector Span'Event
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
         _Span'droppedEventsCount :: Word32
_Span'droppedEventsCount = Word32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _Span'links :: Vector Span'Link
_Span'links = Vector Span'Link
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
         _Span'droppedLinksCount :: Word32
_Span'droppedLinksCount = Word32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _Span'status :: Maybe Status
_Span'status = Maybe Status
forall a. Maybe a
Prelude.Nothing, _Span'_unknownFields :: FieldSet
_Span'_unknownFields = []}
  parseMessage :: Parser Span
parseMessage
    = let
        loop ::
          Span
          -> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld Proto.Opentelemetry.Proto.Common.V1.Common.KeyValue
             -> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld Span'Event
                -> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld Span'Link
                   -> Data.ProtoLens.Encoding.Bytes.Parser Span
        loop :: Span
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Span'Event
-> Growing Vector RealWorld Span'Link
-> Parser Span
loop Span
x Growing Vector RealWorld KeyValue
mutable'attributes Growing Vector RealWorld Span'Event
mutable'events Growing Vector RealWorld Span'Link
mutable'links
          = do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
               if Bool
end then
                   do Vector KeyValue
frozen'attributes <- IO (Vector KeyValue) -> Parser (Vector KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                             (Growing Vector (PrimState IO) KeyValue -> IO (Vector KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
                                                Growing Vector RealWorld KeyValue
Growing Vector (PrimState IO) KeyValue
mutable'attributes)
                      Vector Span'Event
frozen'events <- IO (Vector Span'Event) -> Parser (Vector Span'Event)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                         (Growing Vector (PrimState IO) Span'Event -> IO (Vector Span'Event)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
                                            Growing Vector RealWorld Span'Event
Growing Vector (PrimState IO) Span'Event
mutable'events)
                      Vector Span'Link
frozen'links <- IO (Vector Span'Link) -> Parser (Vector Span'Link)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                        (Growing Vector (PrimState IO) Span'Link -> IO (Vector Span'Link)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze Growing Vector RealWorld Span'Link
Growing Vector (PrimState IO) Span'Link
mutable'links)
                      (let missing :: [a]
missing = []
                       in
                         if [Any] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [Any]
forall a. [a]
missing then
                             () -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
                         else
                             String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
                               (String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
                                  String
"Missing required fields: "
                                  ([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
forall a. [a]
missing :: [Prelude.String]))))
                      Span -> Parser Span
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
                        (Setter Span Span FieldSet FieldSet
-> (FieldSet -> FieldSet) -> Span -> Span
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
                           forall msg. Message msg => Lens' msg FieldSet
Setter Span Span FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
                           (Setter Span Span (Vector KeyValue) (Vector KeyValue)
-> Vector KeyValue -> Span -> Span
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
                              (forall s a (f :: * -> *).
(HasField s "vec'attributes" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'attributes") Vector KeyValue
frozen'attributes
                              (Setter Span Span (Vector Span'Event) (Vector Span'Event)
-> Vector Span'Event -> Span -> Span
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
                                 (forall s a (f :: * -> *).
(HasField s "vec'events" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'events") Vector Span'Event
frozen'events
                                 (Setter Span Span (Vector Span'Link) (Vector Span'Link)
-> Vector Span'Link -> Span -> Span
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
                                    (forall s a (f :: * -> *).
(HasField s "vec'links" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'links") Vector Span'Link
frozen'links Span
x))))
               else
                   do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                      case Word64
tag of
                        Word64
10
                          -> do ByteString
y <- Parser ByteString -> String -> Parser ByteString
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       (do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                           Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
                                             (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len))
                                       String
"trace_id"
                                Span
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Span'Event
-> Growing Vector RealWorld Span'Link
-> Parser Span
loop
                                  (Setter Span Span ByteString ByteString
-> ByteString -> Span -> Span
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "traceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"traceId") ByteString
y Span
x)
                                  Growing Vector RealWorld KeyValue
mutable'attributes Growing Vector RealWorld Span'Event
mutable'events Growing Vector RealWorld Span'Link
mutable'links
                        Word64
18
                          -> do ByteString
y <- Parser ByteString -> String -> Parser ByteString
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       (do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                           Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
                                             (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len))
                                       String
"span_id"
                                Span
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Span'Event
-> Growing Vector RealWorld Span'Link
-> Parser Span
loop
                                  (Setter Span Span ByteString ByteString
-> ByteString -> Span -> Span
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "spanId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"spanId") ByteString
y Span
x)
                                  Growing Vector RealWorld KeyValue
mutable'attributes Growing Vector RealWorld Span'Event
mutable'events Growing Vector RealWorld Span'Link
mutable'links
                        Word64
26
                          -> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       (do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                                       Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
                                                         (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
                                           Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
                                             (case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
                                                (Prelude.Left UnicodeException
err)
                                                  -> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
                                                (Prelude.Right Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
                                       String
"trace_state"
                                Span
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Span'Event
-> Growing Vector RealWorld Span'Link
-> Parser Span
loop
                                  (Setter Span Span Text Text -> Text -> Span -> Span
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "traceState" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"traceState") Text
y Span
x)
                                  Growing Vector RealWorld KeyValue
mutable'attributes Growing Vector RealWorld Span'Event
mutable'events Growing Vector RealWorld Span'Link
mutable'links
                        Word64
34
                          -> do ByteString
y <- Parser ByteString -> String -> Parser ByteString
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       (do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                           Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
                                             (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len))
                                       String
"parent_span_id"
                                Span
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Span'Event
-> Growing Vector RealWorld Span'Link
-> Parser Span
loop
                                  (Setter Span Span ByteString ByteString
-> ByteString -> Span -> Span
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
                                     (forall s a (f :: * -> *).
(HasField s "parentSpanId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"parentSpanId") ByteString
y Span
x)
                                  Growing Vector RealWorld KeyValue
mutable'attributes Growing Vector RealWorld Span'Event
mutable'events Growing Vector RealWorld Span'Link
mutable'links
                        Word64
42
                          -> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       (do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                                       Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
                                                         (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
                                           Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
                                             (case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
                                                (Prelude.Left UnicodeException
err)
                                                  -> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
                                                (Prelude.Right Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
                                       String
"name"
                                Span
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Span'Event
-> Growing Vector RealWorld Span'Link
-> Parser Span
loop
                                  (Setter Span Span Text Text -> Text -> Span -> Span
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "name" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"name") Text
y Span
x)
                                  Growing Vector RealWorld KeyValue
mutable'attributes Growing Vector RealWorld Span'Event
mutable'events Growing Vector RealWorld Span'Link
mutable'links
                        Word64
48
                          -> do Span'SpanKind
y <- Parser Span'SpanKind -> String -> Parser Span'SpanKind
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       ((Int -> Span'SpanKind) -> Parser Int -> Parser Span'SpanKind
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
                                          Int -> Span'SpanKind
forall a. Enum a => Int -> a
Prelude.toEnum
                                          ((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
                                             Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
                                             Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
                                       String
"kind"
                                Span
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Span'Event
-> Growing Vector RealWorld Span'Link
-> Parser Span
loop
                                  (Setter Span Span Span'SpanKind Span'SpanKind
-> Span'SpanKind -> Span -> Span
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "kind" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"kind") Span'SpanKind
y Span
x)
                                  Growing Vector RealWorld KeyValue
mutable'attributes Growing Vector RealWorld Span'Event
mutable'events Growing Vector RealWorld Span'Link
mutable'links
                        Word64
57
                          -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       Parser Word64
Data.ProtoLens.Encoding.Bytes.getFixed64
                                       String
"start_time_unix_nano"
                                Span
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Span'Event
-> Growing Vector RealWorld Span'Link
-> Parser Span
loop
                                  (Setter Span Span Word64 Word64 -> Word64 -> Span -> Span
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
                                     (forall s a (f :: * -> *).
(HasField s "startTimeUnixNano" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"startTimeUnixNano") Word64
y Span
x)
                                  Growing Vector RealWorld KeyValue
mutable'attributes Growing Vector RealWorld Span'Event
mutable'events Growing Vector RealWorld Span'Link
mutable'links
                        Word64
65
                          -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       Parser Word64
Data.ProtoLens.Encoding.Bytes.getFixed64 String
"end_time_unix_nano"
                                Span
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Span'Event
-> Growing Vector RealWorld Span'Link
-> Parser Span
loop
                                  (Setter Span Span Word64 Word64 -> Word64 -> Span -> Span
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
                                     (forall s a (f :: * -> *).
(HasField s "endTimeUnixNano" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"endTimeUnixNano") Word64
y Span
x)
                                  Growing Vector RealWorld KeyValue
mutable'attributes Growing Vector RealWorld Span'Event
mutable'events Growing Vector RealWorld Span'Link
mutable'links
                        Word64
74
                          -> do !KeyValue
y <- Parser KeyValue -> String -> Parser KeyValue
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                        (do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                            Int -> Parser KeyValue -> Parser KeyValue
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
                                              (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
                                              Parser KeyValue
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
                                        String
"attributes"
                                Growing Vector RealWorld KeyValue
v <- IO (Growing Vector RealWorld KeyValue)
-> Parser (Growing Vector RealWorld KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                       (Growing Vector (PrimState IO) KeyValue
-> KeyValue -> IO (Growing Vector (PrimState IO) KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append Growing Vector RealWorld KeyValue
Growing Vector (PrimState IO) KeyValue
mutable'attributes KeyValue
y)
                                Span
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Span'Event
-> Growing Vector RealWorld Span'Link
-> Parser Span
loop Span
x Growing Vector RealWorld KeyValue
v Growing Vector RealWorld Span'Event
mutable'events Growing Vector RealWorld Span'Link
mutable'links
                        Word64
80
                          -> do Word32
y <- Parser Word32 -> String -> Parser Word32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       ((Word64 -> Word32) -> Parser Word64 -> Parser Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
                                          Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
                                          Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
                                       String
"dropped_attributes_count"
                                Span
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Span'Event
-> Growing Vector RealWorld Span'Link
-> Parser Span
loop
                                  (Setter Span Span Word32 Word32 -> Word32 -> Span -> Span
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
                                     (forall s a (f :: * -> *).
(HasField s "droppedAttributesCount" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"droppedAttributesCount") Word32
y Span
x)
                                  Growing Vector RealWorld KeyValue
mutable'attributes Growing Vector RealWorld Span'Event
mutable'events Growing Vector RealWorld Span'Link
mutable'links
                        Word64
90
                          -> do !Span'Event
y <- Parser Span'Event -> String -> Parser Span'Event
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                        (do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                            Int -> Parser Span'Event -> Parser Span'Event
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
                                              (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
                                              Parser Span'Event
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
                                        String
"events"
                                Growing Vector RealWorld Span'Event
v <- IO (Growing Vector RealWorld Span'Event)
-> Parser (Growing Vector RealWorld Span'Event)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                       (Growing Vector (PrimState IO) Span'Event
-> Span'Event -> IO (Growing Vector (PrimState IO) Span'Event)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append Growing Vector RealWorld Span'Event
Growing Vector (PrimState IO) Span'Event
mutable'events Span'Event
y)
                                Span
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Span'Event
-> Growing Vector RealWorld Span'Link
-> Parser Span
loop Span
x Growing Vector RealWorld KeyValue
mutable'attributes Growing Vector RealWorld Span'Event
v Growing Vector RealWorld Span'Link
mutable'links
                        Word64
96
                          -> do Word32
y <- Parser Word32 -> String -> Parser Word32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       ((Word64 -> Word32) -> Parser Word64 -> Parser Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
                                          Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
                                          Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
                                       String
"dropped_events_count"
                                Span
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Span'Event
-> Growing Vector RealWorld Span'Link
-> Parser Span
loop
                                  (Setter Span Span Word32 Word32 -> Word32 -> Span -> Span
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
                                     (forall s a (f :: * -> *).
(HasField s "droppedEventsCount" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"droppedEventsCount") Word32
y Span
x)
                                  Growing Vector RealWorld KeyValue
mutable'attributes Growing Vector RealWorld Span'Event
mutable'events Growing Vector RealWorld Span'Link
mutable'links
                        Word64
106
                          -> do !Span'Link
y <- Parser Span'Link -> String -> Parser Span'Link
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                        (do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                            Int -> Parser Span'Link -> Parser Span'Link
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
                                              (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
                                              Parser Span'Link
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
                                        String
"links"
                                Growing Vector RealWorld Span'Link
v <- IO (Growing Vector RealWorld Span'Link)
-> Parser (Growing Vector RealWorld Span'Link)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                       (Growing Vector (PrimState IO) Span'Link
-> Span'Link -> IO (Growing Vector (PrimState IO) Span'Link)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append Growing Vector RealWorld Span'Link
Growing Vector (PrimState IO) Span'Link
mutable'links Span'Link
y)
                                Span
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Span'Event
-> Growing Vector RealWorld Span'Link
-> Parser Span
loop Span
x Growing Vector RealWorld KeyValue
mutable'attributes Growing Vector RealWorld Span'Event
mutable'events Growing Vector RealWorld Span'Link
v
                        Word64
112
                          -> do Word32
y <- Parser Word32 -> String -> Parser Word32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       ((Word64 -> Word32) -> Parser Word64 -> Parser Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
                                          Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
                                          Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
                                       String
"dropped_links_count"
                                Span
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Span'Event
-> Growing Vector RealWorld Span'Link
-> Parser Span
loop
                                  (Setter Span Span Word32 Word32 -> Word32 -> Span -> Span
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
                                     (forall s a (f :: * -> *).
(HasField s "droppedLinksCount" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"droppedLinksCount") Word32
y Span
x)
                                  Growing Vector RealWorld KeyValue
mutable'attributes Growing Vector RealWorld Span'Event
mutable'events Growing Vector RealWorld Span'Link
mutable'links
                        Word64
122
                          -> do Status
y <- Parser Status -> String -> Parser Status
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       (do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                           Int -> Parser Status -> Parser Status
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
                                             (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len) Parser Status
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
                                       String
"status"
                                Span
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Span'Event
-> Growing Vector RealWorld Span'Link
-> Parser Span
loop
                                  (Setter Span Span Status Status -> Status -> Span -> Span
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "status" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"status") Status
y Span
x)
                                  Growing Vector RealWorld KeyValue
mutable'attributes Growing Vector RealWorld Span'Event
mutable'events Growing Vector RealWorld Span'Link
mutable'links
                        Word64
wire
                          -> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
                                        Word64
wire
                                Span
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Span'Event
-> Growing Vector RealWorld Span'Link
-> Parser Span
loop
                                  (Setter Span Span FieldSet FieldSet
-> (FieldSet -> FieldSet) -> Span -> Span
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
                                     forall msg. Message msg => Lens' msg FieldSet
Setter Span Span FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) Span
x)
                                  Growing Vector RealWorld KeyValue
mutable'attributes Growing Vector RealWorld Span'Event
mutable'events Growing Vector RealWorld Span'Link
mutable'links
      in
        Parser Span -> String -> Parser Span
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
          (do Growing Vector RealWorld KeyValue
mutable'attributes <- IO (Growing Vector RealWorld KeyValue)
-> Parser (Growing Vector RealWorld KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                      IO (Growing Vector RealWorld KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
              Growing Vector RealWorld Span'Event
mutable'events <- IO (Growing Vector RealWorld Span'Event)
-> Parser (Growing Vector RealWorld Span'Event)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                  IO (Growing Vector RealWorld Span'Event)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
              Growing Vector RealWorld Span'Link
mutable'links <- IO (Growing Vector RealWorld Span'Link)
-> Parser (Growing Vector RealWorld Span'Link)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                 IO (Growing Vector RealWorld Span'Link)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
              Span
-> Growing Vector RealWorld KeyValue
-> Growing Vector RealWorld Span'Event
-> Growing Vector RealWorld Span'Link
-> Parser Span
loop
                Span
forall msg. Message msg => msg
Data.ProtoLens.defMessage Growing Vector RealWorld KeyValue
mutable'attributes Growing Vector RealWorld Span'Event
mutable'events
                Growing Vector RealWorld Span'Link
mutable'links)
          String
"Span"
  buildMessage :: Span -> Builder
buildMessage
    = \ Span
_x
        -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
             (let
                _v :: ByteString
_v = FoldLike ByteString Span Span ByteString ByteString
-> Span -> ByteString
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "traceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"traceId") Span
_x
              in
                if ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) ByteString
_v ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                    Builder
forall a. Monoid a => a
Data.Monoid.mempty
                else
                    Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                      (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
10)
                      ((\ ByteString
bs
                          -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                               (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                  (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
                               (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
                         ByteString
_v))
             (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                (let
                   _v :: ByteString
_v = FoldLike ByteString Span Span ByteString ByteString
-> Span -> ByteString
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "spanId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"spanId") Span
_x
                 in
                   if ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) ByteString
_v ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                       Builder
forall a. Monoid a => a
Data.Monoid.mempty
                   else
                       Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                         (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
18)
                         ((\ ByteString
bs
                             -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                  (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                     (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
                                  (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
                            ByteString
_v))
                (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                   (let
                      _v :: Text
_v
                        = FoldLike Text Span Span Text Text -> Span -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "traceState" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"traceState") Span
_x
                    in
                      if Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) Text
_v Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                          Builder
forall a. Monoid a => a
Data.Monoid.mempty
                      else
                          Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                            (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
26)
                            ((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                               (\ ByteString
bs
                                  -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                       (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                          (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
                                       (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
                               Text -> ByteString
Data.Text.Encoding.encodeUtf8 Text
_v))
                   (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                      (let
                         _v :: ByteString
_v
                           = FoldLike ByteString Span Span ByteString ByteString
-> Span -> ByteString
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "parentSpanId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"parentSpanId") Span
_x
                       in
                         if ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) ByteString
_v ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                             Builder
forall a. Monoid a => a
Data.Monoid.mempty
                         else
                             Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                               (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
34)
                               ((\ ByteString
bs
                                   -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                        (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                           (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
                                        (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
                                  ByteString
_v))
                      (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                         (let _v :: Text
_v = FoldLike Text Span Span Text Text -> Span -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "name" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"name") Span
_x
                          in
                            if Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) Text
_v Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                                Builder
forall a. Monoid a => a
Data.Monoid.mempty
                            else
                                Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                  (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
42)
                                  ((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                                     (\ ByteString
bs
                                        -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                             (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                                (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
                                             (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
                                     Text -> ByteString
Data.Text.Encoding.encodeUtf8 Text
_v))
                         (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                            (let _v :: Span'SpanKind
_v = FoldLike Span'SpanKind Span Span Span'SpanKind Span'SpanKind
-> Span -> Span'SpanKind
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "kind" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"kind") Span
_x
                             in
                               if Span'SpanKind -> Span'SpanKind -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) Span'SpanKind
_v Span'SpanKind
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                                   Builder
forall a. Monoid a => a
Data.Monoid.mempty
                               else
                                   Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                     (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
48)
                                     ((Int -> Builder)
-> (Span'SpanKind -> Int) -> Span'SpanKind -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                                        ((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                                           Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                           Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
                                        Span'SpanKind -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum Span'SpanKind
_v))
                            (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                               (let
                                  _v :: Word64
_v
                                    = FoldLike Word64 Span Span Word64 Word64 -> Span -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
                                        (forall s a (f :: * -> *).
(HasField s "startTimeUnixNano" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"startTimeUnixNano") Span
_x
                                in
                                  if Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) Word64
_v Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                                      Builder
forall a. Monoid a => a
Data.Monoid.mempty
                                  else
                                      Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                        (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
57)
                                        (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putFixed64 Word64
_v))
                               (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                  (let
                                     _v :: Word64
_v
                                       = FoldLike Word64 Span Span Word64 Word64 -> Span -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
                                           (forall s a (f :: * -> *).
(HasField s "endTimeUnixNano" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"endTimeUnixNano") Span
_x
                                   in
                                     if Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) Word64
_v Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                                         Builder
forall a. Monoid a => a
Data.Monoid.mempty
                                     else
                                         Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                           (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
65)
                                           (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putFixed64 Word64
_v))
                                  (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                     ((KeyValue -> Builder) -> Vector KeyValue -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
                                        (\ KeyValue
_v
                                           -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                                (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
74)
                                                ((ByteString -> Builder)
-> (KeyValue -> ByteString) -> KeyValue -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                                                   (\ ByteString
bs
                                                      -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                                           (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                                              (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
                                                                 (ByteString -> Int
Data.ByteString.length ByteString
bs)))
                                                           (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
                                                              ByteString
bs))
                                                   KeyValue -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage KeyValue
_v))
                                        (FoldLike
  (Vector KeyValue) Span Span (Vector KeyValue) (Vector KeyValue)
-> Span -> Vector KeyValue
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
                                           (forall s a (f :: * -> *).
(HasField s "vec'attributes" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'attributes") Span
_x))
                                     (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                        (let
                                           _v :: Word32
_v
                                             = FoldLike Word32 Span Span Word32 Word32 -> Span -> Word32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
                                                 (forall s a (f :: * -> *).
(HasField s "droppedAttributesCount" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
                                                    @"droppedAttributesCount")
                                                 Span
_x
                                         in
                                           if Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) Word32
_v Word32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                                               Builder
forall a. Monoid a => a
Data.Monoid.mempty
                                           else
                                               Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                                 (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
80)
                                                 ((Word64 -> Builder) -> (Word32 -> Word64) -> Word32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                                                    Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                                    Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word32
_v))
                                        (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                           ((Span'Event -> Builder) -> Vector Span'Event -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
                                              (\ Span'Event
_v
                                                 -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                                      (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
90)
                                                      ((ByteString -> Builder)
-> (Span'Event -> ByteString) -> Span'Event -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                                                         (\ ByteString
bs
                                                            -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                                                 (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                                                    (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
                                                                       (ByteString -> Int
Data.ByteString.length ByteString
bs)))
                                                                 (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
                                                                    ByteString
bs))
                                                         Span'Event -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage Span'Event
_v))
                                              (FoldLike
  (Vector Span'Event)
  Span
  Span
  (Vector Span'Event)
  (Vector Span'Event)
-> Span -> Vector Span'Event
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
                                                 (forall s a (f :: * -> *).
(HasField s "vec'events" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'events") Span
_x))
                                           (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                              (let
                                                 _v :: Word32
_v
                                                   = FoldLike Word32 Span Span Word32 Word32 -> Span -> Word32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
                                                       (forall s a (f :: * -> *).
(HasField s "droppedEventsCount" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
                                                          @"droppedEventsCount")
                                                       Span
_x
                                               in
                                                 if Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) Word32
_v Word32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                                                     Builder
forall a. Monoid a => a
Data.Monoid.mempty
                                                 else
                                                     Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                                       (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
96)
                                                       ((Word64 -> Builder) -> (Word32 -> Word64) -> Word32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                                                          Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                                          Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word32
_v))
                                              (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                                 ((Span'Link -> Builder) -> Vector Span'Link -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
                                                    (\ Span'Link
_v
                                                       -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                                            (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                                               Word64
106)
                                                            ((ByteString -> Builder)
-> (Span'Link -> ByteString) -> Span'Link -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                                                               (\ ByteString
bs
                                                                  -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                                                       (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                                                          (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
                                                                             (ByteString -> Int
Data.ByteString.length
                                                                                ByteString
bs)))
                                                                       (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
                                                                          ByteString
bs))
                                                               Span'Link -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage Span'Link
_v))
                                                    (FoldLike
  (Vector Span'Link) Span Span (Vector Span'Link) (Vector Span'Link)
-> Span -> Vector Span'Link
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
                                                       (forall s a (f :: * -> *).
(HasField s "vec'links" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'links")
                                                       Span
_x))
                                                 (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                                    (let
                                                       _v :: Word32
_v
                                                         = FoldLike Word32 Span Span Word32 Word32 -> Span -> Word32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
                                                             (forall s a (f :: * -> *).
(HasField s "droppedLinksCount" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
                                                                @"droppedLinksCount")
                                                             Span
_x
                                                     in
                                                       if Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==)
                                                            Word32
_v Word32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                                                           Builder
forall a. Monoid a => a
Data.Monoid.mempty
                                                       else
                                                           Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                                             (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                                                Word64
112)
                                                             ((Word64 -> Builder) -> (Word32 -> Word64) -> Word32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                                                                Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                                                Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word32
_v))
                                                    (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                                       (case
                                                            FoldLike (Maybe Status) Span Span (Maybe Status) (Maybe Status)
-> Span -> Maybe Status
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
                                                              (forall s a (f :: * -> *).
(HasField s "maybe'status" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field
                                                                 @"maybe'status")
                                                              Span
_x
                                                        of
                                                          Maybe Status
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
                                                          (Prelude.Just Status
_v)
                                                            -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                                                 (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                                                    Word64
122)
                                                                 ((ByteString -> Builder)
-> (Status -> ByteString) -> Status -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                                                                    (\ ByteString
bs
                                                                       -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                                                            (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                                                               (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
                                                                                  (ByteString -> Int
Data.ByteString.length
                                                                                     ByteString
bs)))
                                                                            (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes
                                                                               ByteString
bs))
                                                                    Status -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage
                                                                    Status
_v))
                                                       (FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
                                                          (FoldLike FieldSet Span Span FieldSet FieldSet -> Span -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
                                                             FoldLike FieldSet Span Span FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields
                                                             Span
_x))))))))))))))))
instance Control.DeepSeq.NFData Span where
  rnf :: Span -> ()
rnf
    = \ Span
x__
        -> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
             (Span -> FieldSet
_Span'_unknownFields Span
x__)
             (ByteString -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                (Span -> ByteString
_Span'traceId Span
x__)
                (ByteString -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                   (Span -> ByteString
_Span'spanId Span
x__)
                   (Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                      (Span -> Text
_Span'traceState Span
x__)
                      (ByteString -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                         (Span -> ByteString
_Span'parentSpanId Span
x__)
                         (Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                            (Span -> Text
_Span'name Span
x__)
                            (Span'SpanKind -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                               (Span -> Span'SpanKind
_Span'kind Span
x__)
                               (Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                                  (Span -> Word64
_Span'startTimeUnixNano Span
x__)
                                  (Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                                     (Span -> Word64
_Span'endTimeUnixNano Span
x__)
                                     (Vector KeyValue -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                                        (Span -> Vector KeyValue
_Span'attributes Span
x__)
                                        (Word32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                                           (Span -> Word32
_Span'droppedAttributesCount Span
x__)
                                           (Vector Span'Event -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                                              (Span -> Vector Span'Event
_Span'events Span
x__)
                                              (Word32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                                                 (Span -> Word32
_Span'droppedEventsCount Span
x__)
                                                 (Vector Span'Link -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                                                    (Span -> Vector Span'Link
_Span'links Span
x__)
                                                    (Word32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                                                       (Span -> Word32
_Span'droppedLinksCount Span
x__)
                                                       (Maybe Status -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                                                          (Span -> Maybe Status
_Span'status Span
x__) ())))))))))))))))
{- | Fields :
     
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.timeUnixNano' @:: Lens' Span'Event Data.Word.Word64@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.name' @:: Lens' Span'Event Data.Text.Text@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.attributes' @:: Lens' Span'Event [Proto.Opentelemetry.Proto.Common.V1.Common.KeyValue]@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.vec'attributes' @:: Lens' Span'Event (Data.Vector.Vector Proto.Opentelemetry.Proto.Common.V1.Common.KeyValue)@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.droppedAttributesCount' @:: Lens' Span'Event Data.Word.Word32@ -}
data Span'Event
  = Span'Event'_constructor {Span'Event -> Word64
_Span'Event'timeUnixNano :: !Data.Word.Word64,
                             Span'Event -> Text
_Span'Event'name :: !Data.Text.Text,
                             Span'Event -> Vector KeyValue
_Span'Event'attributes :: !(Data.Vector.Vector Proto.Opentelemetry.Proto.Common.V1.Common.KeyValue),
                             Span'Event -> Word32
_Span'Event'droppedAttributesCount :: !Data.Word.Word32,
                             Span'Event -> FieldSet
_Span'Event'_unknownFields :: !Data.ProtoLens.FieldSet}
  deriving stock (Span'Event -> Span'Event -> Bool
(Span'Event -> Span'Event -> Bool)
-> (Span'Event -> Span'Event -> Bool) -> Eq Span'Event
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Span'Event -> Span'Event -> Bool
$c/= :: Span'Event -> Span'Event -> Bool
== :: Span'Event -> Span'Event -> Bool
$c== :: Span'Event -> Span'Event -> Bool
Prelude.Eq, Eq Span'Event
Eq Span'Event
-> (Span'Event -> Span'Event -> Ordering)
-> (Span'Event -> Span'Event -> Bool)
-> (Span'Event -> Span'Event -> Bool)
-> (Span'Event -> Span'Event -> Bool)
-> (Span'Event -> Span'Event -> Bool)
-> (Span'Event -> Span'Event -> Span'Event)
-> (Span'Event -> Span'Event -> Span'Event)
-> Ord Span'Event
Span'Event -> Span'Event -> Bool
Span'Event -> Span'Event -> Ordering
Span'Event -> Span'Event -> Span'Event
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 :: Span'Event -> Span'Event -> Span'Event
$cmin :: Span'Event -> Span'Event -> Span'Event
max :: Span'Event -> Span'Event -> Span'Event
$cmax :: Span'Event -> Span'Event -> Span'Event
>= :: Span'Event -> Span'Event -> Bool
$c>= :: Span'Event -> Span'Event -> Bool
> :: Span'Event -> Span'Event -> Bool
$c> :: Span'Event -> Span'Event -> Bool
<= :: Span'Event -> Span'Event -> Bool
$c<= :: Span'Event -> Span'Event -> Bool
< :: Span'Event -> Span'Event -> Bool
$c< :: Span'Event -> Span'Event -> Bool
compare :: Span'Event -> Span'Event -> Ordering
$ccompare :: Span'Event -> Span'Event -> Ordering
$cp1Ord :: Eq Span'Event
Prelude.Ord)
instance Prelude.Show Span'Event where
  showsPrec :: Int -> Span'Event -> ShowS
showsPrec Int
_ Span'Event
__x String
__s
    = Char -> ShowS
Prelude.showChar
        Char
'{'
        (String -> ShowS
Prelude.showString
           (Span'Event -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort Span'Event
__x) (Char -> ShowS
Prelude.showChar Char
'}' String
__s))
instance Data.ProtoLens.Field.HasField Span'Event "timeUnixNano" Data.Word.Word64 where
  fieldOf :: Proxy# "timeUnixNano"
-> (Word64 -> f Word64) -> Span'Event -> f Span'Event
fieldOf Proxy# "timeUnixNano"
_
    = ((Word64 -> f Word64) -> Span'Event -> f Span'Event)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> Span'Event
-> f Span'Event
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span'Event -> Word64)
-> (Span'Event -> Word64 -> Span'Event)
-> Lens Span'Event Span'Event Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span'Event -> Word64
_Span'Event'timeUnixNano
           (\ Span'Event
x__ Word64
y__ -> Span'Event
x__ {_Span'Event'timeUnixNano :: Word64
_Span'Event'timeUnixNano = Word64
y__}))
        (Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Span'Event "name" Data.Text.Text where
  fieldOf :: Proxy# "name" -> (Text -> f Text) -> Span'Event -> f Span'Event
fieldOf Proxy# "name"
_
    = ((Text -> f Text) -> Span'Event -> f Span'Event)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> Span'Event
-> f Span'Event
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span'Event -> Text)
-> (Span'Event -> Text -> Span'Event)
-> Lens Span'Event Span'Event Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span'Event -> Text
_Span'Event'name (\ Span'Event
x__ Text
y__ -> Span'Event
x__ {_Span'Event'name :: Text
_Span'Event'name = Text
y__}))
        (Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Span'Event "attributes" [Proto.Opentelemetry.Proto.Common.V1.Common.KeyValue] where
  fieldOf :: Proxy# "attributes"
-> ([KeyValue] -> f [KeyValue]) -> Span'Event -> f Span'Event
fieldOf Proxy# "attributes"
_
    = ((Vector KeyValue -> f (Vector KeyValue))
 -> Span'Event -> f Span'Event)
-> (([KeyValue] -> f [KeyValue])
    -> Vector KeyValue -> f (Vector KeyValue))
-> ([KeyValue] -> f [KeyValue])
-> Span'Event
-> f Span'Event
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span'Event -> Vector KeyValue)
-> (Span'Event -> Vector KeyValue -> Span'Event)
-> Lens Span'Event Span'Event (Vector KeyValue) (Vector KeyValue)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span'Event -> Vector KeyValue
_Span'Event'attributes
           (\ Span'Event
x__ Vector KeyValue
y__ -> Span'Event
x__ {_Span'Event'attributes :: Vector KeyValue
_Span'Event'attributes = Vector KeyValue
y__}))
        ((Vector KeyValue -> [KeyValue])
-> (Vector KeyValue -> [KeyValue] -> Vector KeyValue)
-> Lens (Vector KeyValue) (Vector KeyValue) [KeyValue] [KeyValue]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Vector KeyValue -> [KeyValue]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
           (\ Vector KeyValue
_ [KeyValue]
y__ -> [KeyValue] -> Vector KeyValue
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [KeyValue]
y__))
instance Data.ProtoLens.Field.HasField Span'Event "vec'attributes" (Data.Vector.Vector Proto.Opentelemetry.Proto.Common.V1.Common.KeyValue) where
  fieldOf :: Proxy# "vec'attributes"
-> (Vector KeyValue -> f (Vector KeyValue))
-> Span'Event
-> f Span'Event
fieldOf Proxy# "vec'attributes"
_
    = ((Vector KeyValue -> f (Vector KeyValue))
 -> Span'Event -> f Span'Event)
-> ((Vector KeyValue -> f (Vector KeyValue))
    -> Vector KeyValue -> f (Vector KeyValue))
-> (Vector KeyValue -> f (Vector KeyValue))
-> Span'Event
-> f Span'Event
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span'Event -> Vector KeyValue)
-> (Span'Event -> Vector KeyValue -> Span'Event)
-> Lens Span'Event Span'Event (Vector KeyValue) (Vector KeyValue)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span'Event -> Vector KeyValue
_Span'Event'attributes
           (\ Span'Event
x__ Vector KeyValue
y__ -> Span'Event
x__ {_Span'Event'attributes :: Vector KeyValue
_Span'Event'attributes = Vector KeyValue
y__}))
        (Vector KeyValue -> f (Vector KeyValue))
-> Vector KeyValue -> f (Vector KeyValue)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Span'Event "droppedAttributesCount" Data.Word.Word32 where
  fieldOf :: Proxy# "droppedAttributesCount"
-> (Word32 -> f Word32) -> Span'Event -> f Span'Event
fieldOf Proxy# "droppedAttributesCount"
_
    = ((Word32 -> f Word32) -> Span'Event -> f Span'Event)
-> ((Word32 -> f Word32) -> Word32 -> f Word32)
-> (Word32 -> f Word32)
-> Span'Event
-> f Span'Event
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span'Event -> Word32)
-> (Span'Event -> Word32 -> Span'Event)
-> Lens Span'Event Span'Event Word32 Word32
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span'Event -> Word32
_Span'Event'droppedAttributesCount
           (\ Span'Event
x__ Word32
y__ -> Span'Event
x__ {_Span'Event'droppedAttributesCount :: Word32
_Span'Event'droppedAttributesCount = Word32
y__}))
        (Word32 -> f Word32) -> Word32 -> f Word32
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message Span'Event where
  messageName :: Proxy Span'Event -> Text
messageName Proxy Span'Event
_
    = String -> Text
Data.Text.pack String
"opentelemetry.proto.trace.v1.Span.Event"
  packedMessageDescriptor :: Proxy Span'Event -> ByteString
packedMessageDescriptor Proxy Span'Event
_
    = ByteString
"\n\
      \\ENQEvent\DC2$\n\
      \\SOtime_unix_nano\CAN\SOH \SOH(\ACKR\ftimeUnixNano\DC2\DC2\n\
      \\EOTname\CAN\STX \SOH(\tR\EOTname\DC2G\n\
      \\n\
      \attributes\CAN\ETX \ETX(\v2'.opentelemetry.proto.common.v1.KeyValueR\n\
      \attributes\DC28\n\
      \\CANdropped_attributes_count\CAN\EOT \SOH(\rR\SYNdroppedAttributesCount"
  packedFileDescriptor :: Proxy Span'Event -> ByteString
packedFileDescriptor Proxy Span'Event
_ = ByteString
packedFileDescriptor
  fieldsByTag :: Map Tag (FieldDescriptor Span'Event)
fieldsByTag
    = let
        timeUnixNano__field_descriptor :: FieldDescriptor Span'Event
timeUnixNano__field_descriptor
          = String
-> FieldTypeDescriptor Word64
-> FieldAccessor Span'Event Word64
-> FieldDescriptor Span'Event
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"time_unix_nano"
              (ScalarField Word64 -> FieldTypeDescriptor Word64
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word64
Data.ProtoLens.Fixed64Field ::
                 Data.ProtoLens.FieldTypeDescriptor Data.Word.Word64)
              (WireDefault Word64
-> Lens Span'Event Span'Event Word64 Word64
-> FieldAccessor Span'Event Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault Word64
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional
                 (forall s a (f :: * -> *).
(HasField s "timeUnixNano" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"timeUnixNano")) ::
              Data.ProtoLens.FieldDescriptor Span'Event
        name__field_descriptor :: FieldDescriptor Span'Event
name__field_descriptor
          = String
-> FieldTypeDescriptor Text
-> FieldAccessor Span'Event Text
-> FieldDescriptor Span'Event
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"name"
              (ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
                 Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
              (WireDefault Text
-> Lens Span'Event Span'Event Text Text
-> FieldAccessor Span'Event Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault Text
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional (forall s a (f :: * -> *).
(HasField s "name" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"name")) ::
              Data.ProtoLens.FieldDescriptor Span'Event
        attributes__field_descriptor :: FieldDescriptor Span'Event
attributes__field_descriptor
          = String
-> FieldTypeDescriptor KeyValue
-> FieldAccessor Span'Event KeyValue
-> FieldDescriptor Span'Event
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"attributes"
              (MessageOrGroup -> FieldTypeDescriptor KeyValue
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
                 Data.ProtoLens.FieldTypeDescriptor Proto.Opentelemetry.Proto.Common.V1.Common.KeyValue)
              (Packing
-> Lens' Span'Event [KeyValue] -> FieldAccessor Span'Event KeyValue
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
                 Packing
Data.ProtoLens.Unpacked
                 (forall s a (f :: * -> *).
(HasField s "attributes" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"attributes")) ::
              Data.ProtoLens.FieldDescriptor Span'Event
        droppedAttributesCount__field_descriptor :: FieldDescriptor Span'Event
droppedAttributesCount__field_descriptor
          = String
-> FieldTypeDescriptor Word32
-> FieldAccessor Span'Event Word32
-> FieldDescriptor Span'Event
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"dropped_attributes_count"
              (ScalarField Word32 -> FieldTypeDescriptor Word32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word32
Data.ProtoLens.UInt32Field ::
                 Data.ProtoLens.FieldTypeDescriptor Data.Word.Word32)
              (WireDefault Word32
-> Lens Span'Event Span'Event Word32 Word32
-> FieldAccessor Span'Event Word32
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault Word32
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional
                 (forall s a (f :: * -> *).
(HasField s "droppedAttributesCount" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"droppedAttributesCount")) ::
              Data.ProtoLens.FieldDescriptor Span'Event
      in
        [(Tag, FieldDescriptor Span'Event)]
-> Map Tag (FieldDescriptor Span'Event)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
          [(Int -> Tag
Data.ProtoLens.Tag Int
1, FieldDescriptor Span'Event
timeUnixNano__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
2, FieldDescriptor Span'Event
name__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
3, FieldDescriptor Span'Event
attributes__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
4, FieldDescriptor Span'Event
droppedAttributesCount__field_descriptor)]
  unknownFields :: LensLike' f Span'Event FieldSet
unknownFields
    = (Span'Event -> FieldSet)
-> (Span'Event -> FieldSet -> Span'Event)
-> Lens' Span'Event FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
        Span'Event -> FieldSet
_Span'Event'_unknownFields
        (\ Span'Event
x__ FieldSet
y__ -> Span'Event
x__ {_Span'Event'_unknownFields :: FieldSet
_Span'Event'_unknownFields = FieldSet
y__})
  defMessage :: Span'Event
defMessage
    = Span'Event'_constructor :: Word64
-> Text -> Vector KeyValue -> Word32 -> FieldSet -> Span'Event
Span'Event'_constructor
        {_Span'Event'timeUnixNano :: Word64
_Span'Event'timeUnixNano = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _Span'Event'name :: Text
_Span'Event'name = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _Span'Event'attributes :: Vector KeyValue
_Span'Event'attributes = Vector KeyValue
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
         _Span'Event'droppedAttributesCount :: Word32
_Span'Event'droppedAttributesCount = Word32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _Span'Event'_unknownFields :: FieldSet
_Span'Event'_unknownFields = []}
  parseMessage :: Parser Span'Event
parseMessage
    = let
        loop ::
          Span'Event
          -> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld Proto.Opentelemetry.Proto.Common.V1.Common.KeyValue
             -> Data.ProtoLens.Encoding.Bytes.Parser Span'Event
        loop :: Span'Event
-> Growing Vector RealWorld KeyValue -> Parser Span'Event
loop Span'Event
x Growing Vector RealWorld KeyValue
mutable'attributes
          = do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
               if Bool
end then
                   do Vector KeyValue
frozen'attributes <- IO (Vector KeyValue) -> Parser (Vector KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                             (Growing Vector (PrimState IO) KeyValue -> IO (Vector KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
                                                Growing Vector RealWorld KeyValue
Growing Vector (PrimState IO) KeyValue
mutable'attributes)
                      (let missing :: [a]
missing = []
                       in
                         if [Any] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [Any]
forall a. [a]
missing then
                             () -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
                         else
                             String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
                               (String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
                                  String
"Missing required fields: "
                                  ([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
forall a. [a]
missing :: [Prelude.String]))))
                      Span'Event -> Parser Span'Event
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
                        (Setter Span'Event Span'Event FieldSet FieldSet
-> (FieldSet -> FieldSet) -> Span'Event -> Span'Event
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
                           forall msg. Message msg => Lens' msg FieldSet
Setter Span'Event Span'Event FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
                           (Setter Span'Event Span'Event (Vector KeyValue) (Vector KeyValue)
-> Vector KeyValue -> Span'Event -> Span'Event
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
                              (forall s a (f :: * -> *).
(HasField s "vec'attributes" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'attributes") Vector KeyValue
frozen'attributes
                              Span'Event
x))
               else
                   do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                      case Word64
tag of
                        Word64
9 -> do Word64
y <- Parser Word64 -> String -> Parser Word64
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       Parser Word64
Data.ProtoLens.Encoding.Bytes.getFixed64 String
"time_unix_nano"
                                Span'Event
-> Growing Vector RealWorld KeyValue -> Parser Span'Event
loop
                                  (Setter Span'Event Span'Event Word64 Word64
-> Word64 -> Span'Event -> Span'Event
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
                                     (forall s a (f :: * -> *).
(HasField s "timeUnixNano" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"timeUnixNano") Word64
y Span'Event
x)
                                  Growing Vector RealWorld KeyValue
mutable'attributes
                        Word64
18
                          -> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       (do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                                       Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
                                                         (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
                                           Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
                                             (case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
                                                (Prelude.Left UnicodeException
err)
                                                  -> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
                                                (Prelude.Right Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
                                       String
"name"
                                Span'Event
-> Growing Vector RealWorld KeyValue -> Parser Span'Event
loop
                                  (Setter Span'Event Span'Event Text Text
-> Text -> Span'Event -> Span'Event
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "name" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"name") Text
y Span'Event
x)
                                  Growing Vector RealWorld KeyValue
mutable'attributes
                        Word64
26
                          -> do !KeyValue
y <- Parser KeyValue -> String -> Parser KeyValue
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                        (do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                            Int -> Parser KeyValue -> Parser KeyValue
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
                                              (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
                                              Parser KeyValue
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
                                        String
"attributes"
                                Growing Vector RealWorld KeyValue
v <- IO (Growing Vector RealWorld KeyValue)
-> Parser (Growing Vector RealWorld KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                       (Growing Vector (PrimState IO) KeyValue
-> KeyValue -> IO (Growing Vector (PrimState IO) KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append Growing Vector RealWorld KeyValue
Growing Vector (PrimState IO) KeyValue
mutable'attributes KeyValue
y)
                                Span'Event
-> Growing Vector RealWorld KeyValue -> Parser Span'Event
loop Span'Event
x Growing Vector RealWorld KeyValue
v
                        Word64
32
                          -> do Word32
y <- Parser Word32 -> String -> Parser Word32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       ((Word64 -> Word32) -> Parser Word64 -> Parser Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
                                          Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
                                          Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
                                       String
"dropped_attributes_count"
                                Span'Event
-> Growing Vector RealWorld KeyValue -> Parser Span'Event
loop
                                  (Setter Span'Event Span'Event Word32 Word32
-> Word32 -> Span'Event -> Span'Event
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
                                     (forall s a (f :: * -> *).
(HasField s "droppedAttributesCount" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"droppedAttributesCount") Word32
y Span'Event
x)
                                  Growing Vector RealWorld KeyValue
mutable'attributes
                        Word64
wire
                          -> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
                                        Word64
wire
                                Span'Event
-> Growing Vector RealWorld KeyValue -> Parser Span'Event
loop
                                  (Setter Span'Event Span'Event FieldSet FieldSet
-> (FieldSet -> FieldSet) -> Span'Event -> Span'Event
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
                                     forall msg. Message msg => Lens' msg FieldSet
Setter Span'Event Span'Event FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) Span'Event
x)
                                  Growing Vector RealWorld KeyValue
mutable'attributes
      in
        Parser Span'Event -> String -> Parser Span'Event
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
          (do Growing Vector RealWorld KeyValue
mutable'attributes <- IO (Growing Vector RealWorld KeyValue)
-> Parser (Growing Vector RealWorld KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                      IO (Growing Vector RealWorld KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
              Span'Event
-> Growing Vector RealWorld KeyValue -> Parser Span'Event
loop Span'Event
forall msg. Message msg => msg
Data.ProtoLens.defMessage Growing Vector RealWorld KeyValue
mutable'attributes)
          String
"Event"
  buildMessage :: Span'Event -> Builder
buildMessage
    = \ Span'Event
_x
        -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
             (let
                _v :: Word64
_v
                  = FoldLike Word64 Span'Event Span'Event Word64 Word64
-> Span'Event -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "timeUnixNano" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"timeUnixNano") Span'Event
_x
              in
                if Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) Word64
_v Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                    Builder
forall a. Monoid a => a
Data.Monoid.mempty
                else
                    Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                      (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
9)
                      (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putFixed64 Word64
_v))
             (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                (let _v :: Text
_v = FoldLike Text Span'Event Span'Event Text Text -> Span'Event -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "name" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"name") Span'Event
_x
                 in
                   if Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) Text
_v Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                       Builder
forall a. Monoid a => a
Data.Monoid.mempty
                   else
                       Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                         (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
18)
                         ((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                            (\ ByteString
bs
                               -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                    (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                       (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
                                    (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
                            Text -> ByteString
Data.Text.Encoding.encodeUtf8 Text
_v))
                (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                   ((KeyValue -> Builder) -> Vector KeyValue -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
                      (\ KeyValue
_v
                         -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                              (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
26)
                              ((ByteString -> Builder)
-> (KeyValue -> ByteString) -> KeyValue -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                                 (\ ByteString
bs
                                    -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                         (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                            (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
                                         (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
                                 KeyValue -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage KeyValue
_v))
                      (FoldLike
  (Vector KeyValue)
  Span'Event
  Span'Event
  (Vector KeyValue)
  (Vector KeyValue)
-> Span'Event -> Vector KeyValue
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
                         (forall s a (f :: * -> *).
(HasField s "vec'attributes" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'attributes") Span'Event
_x))
                   (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                      (let
                         _v :: Word32
_v
                           = FoldLike Word32 Span'Event Span'Event Word32 Word32
-> Span'Event -> Word32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
                               (forall s a (f :: * -> *).
(HasField s "droppedAttributesCount" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"droppedAttributesCount") Span'Event
_x
                       in
                         if Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) Word32
_v Word32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                             Builder
forall a. Monoid a => a
Data.Monoid.mempty
                         else
                             Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                               (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
32)
                               ((Word64 -> Builder) -> (Word32 -> Word64) -> Word32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                                  Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word32
_v))
                      (FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
                         (FoldLike FieldSet Span'Event Span'Event FieldSet FieldSet
-> Span'Event -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet Span'Event Span'Event FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields Span'Event
_x)))))
instance Control.DeepSeq.NFData Span'Event where
  rnf :: Span'Event -> ()
rnf
    = \ Span'Event
x__
        -> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
             (Span'Event -> FieldSet
_Span'Event'_unknownFields Span'Event
x__)
             (Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                (Span'Event -> Word64
_Span'Event'timeUnixNano Span'Event
x__)
                (Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                   (Span'Event -> Text
_Span'Event'name Span'Event
x__)
                   (Vector KeyValue -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                      (Span'Event -> Vector KeyValue
_Span'Event'attributes Span'Event
x__)
                      (Word32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                         (Span'Event -> Word32
_Span'Event'droppedAttributesCount Span'Event
x__) ()))))
{- | Fields :
     
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.traceId' @:: Lens' Span'Link Data.ByteString.ByteString@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.spanId' @:: Lens' Span'Link Data.ByteString.ByteString@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.traceState' @:: Lens' Span'Link Data.Text.Text@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.attributes' @:: Lens' Span'Link [Proto.Opentelemetry.Proto.Common.V1.Common.KeyValue]@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.vec'attributes' @:: Lens' Span'Link (Data.Vector.Vector Proto.Opentelemetry.Proto.Common.V1.Common.KeyValue)@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.droppedAttributesCount' @:: Lens' Span'Link Data.Word.Word32@ -}
data Span'Link
  = Span'Link'_constructor {Span'Link -> ByteString
_Span'Link'traceId :: !Data.ByteString.ByteString,
                            Span'Link -> ByteString
_Span'Link'spanId :: !Data.ByteString.ByteString,
                            Span'Link -> Text
_Span'Link'traceState :: !Data.Text.Text,
                            Span'Link -> Vector KeyValue
_Span'Link'attributes :: !(Data.Vector.Vector Proto.Opentelemetry.Proto.Common.V1.Common.KeyValue),
                            Span'Link -> Word32
_Span'Link'droppedAttributesCount :: !Data.Word.Word32,
                            Span'Link -> FieldSet
_Span'Link'_unknownFields :: !Data.ProtoLens.FieldSet}
  deriving stock (Span'Link -> Span'Link -> Bool
(Span'Link -> Span'Link -> Bool)
-> (Span'Link -> Span'Link -> Bool) -> Eq Span'Link
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Span'Link -> Span'Link -> Bool
$c/= :: Span'Link -> Span'Link -> Bool
== :: Span'Link -> Span'Link -> Bool
$c== :: Span'Link -> Span'Link -> Bool
Prelude.Eq, Eq Span'Link
Eq Span'Link
-> (Span'Link -> Span'Link -> Ordering)
-> (Span'Link -> Span'Link -> Bool)
-> (Span'Link -> Span'Link -> Bool)
-> (Span'Link -> Span'Link -> Bool)
-> (Span'Link -> Span'Link -> Bool)
-> (Span'Link -> Span'Link -> Span'Link)
-> (Span'Link -> Span'Link -> Span'Link)
-> Ord Span'Link
Span'Link -> Span'Link -> Bool
Span'Link -> Span'Link -> Ordering
Span'Link -> Span'Link -> Span'Link
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 :: Span'Link -> Span'Link -> Span'Link
$cmin :: Span'Link -> Span'Link -> Span'Link
max :: Span'Link -> Span'Link -> Span'Link
$cmax :: Span'Link -> Span'Link -> Span'Link
>= :: Span'Link -> Span'Link -> Bool
$c>= :: Span'Link -> Span'Link -> Bool
> :: Span'Link -> Span'Link -> Bool
$c> :: Span'Link -> Span'Link -> Bool
<= :: Span'Link -> Span'Link -> Bool
$c<= :: Span'Link -> Span'Link -> Bool
< :: Span'Link -> Span'Link -> Bool
$c< :: Span'Link -> Span'Link -> Bool
compare :: Span'Link -> Span'Link -> Ordering
$ccompare :: Span'Link -> Span'Link -> Ordering
$cp1Ord :: Eq Span'Link
Prelude.Ord)
instance Prelude.Show Span'Link where
  showsPrec :: Int -> Span'Link -> ShowS
showsPrec Int
_ Span'Link
__x String
__s
    = Char -> ShowS
Prelude.showChar
        Char
'{'
        (String -> ShowS
Prelude.showString
           (Span'Link -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort Span'Link
__x) (Char -> ShowS
Prelude.showChar Char
'}' String
__s))
instance Data.ProtoLens.Field.HasField Span'Link "traceId" Data.ByteString.ByteString where
  fieldOf :: Proxy# "traceId"
-> (ByteString -> f ByteString) -> Span'Link -> f Span'Link
fieldOf Proxy# "traceId"
_
    = ((ByteString -> f ByteString) -> Span'Link -> f Span'Link)
-> ((ByteString -> f ByteString) -> ByteString -> f ByteString)
-> (ByteString -> f ByteString)
-> Span'Link
-> f Span'Link
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span'Link -> ByteString)
-> (Span'Link -> ByteString -> Span'Link)
-> Lens Span'Link Span'Link ByteString ByteString
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span'Link -> ByteString
_Span'Link'traceId (\ Span'Link
x__ ByteString
y__ -> Span'Link
x__ {_Span'Link'traceId :: ByteString
_Span'Link'traceId = ByteString
y__}))
        (ByteString -> f ByteString) -> ByteString -> f ByteString
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Span'Link "spanId" Data.ByteString.ByteString where
  fieldOf :: Proxy# "spanId"
-> (ByteString -> f ByteString) -> Span'Link -> f Span'Link
fieldOf Proxy# "spanId"
_
    = ((ByteString -> f ByteString) -> Span'Link -> f Span'Link)
-> ((ByteString -> f ByteString) -> ByteString -> f ByteString)
-> (ByteString -> f ByteString)
-> Span'Link
-> f Span'Link
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span'Link -> ByteString)
-> (Span'Link -> ByteString -> Span'Link)
-> Lens Span'Link Span'Link ByteString ByteString
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span'Link -> ByteString
_Span'Link'spanId (\ Span'Link
x__ ByteString
y__ -> Span'Link
x__ {_Span'Link'spanId :: ByteString
_Span'Link'spanId = ByteString
y__}))
        (ByteString -> f ByteString) -> ByteString -> f ByteString
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Span'Link "traceState" Data.Text.Text where
  fieldOf :: Proxy# "traceState" -> (Text -> f Text) -> Span'Link -> f Span'Link
fieldOf Proxy# "traceState"
_
    = ((Text -> f Text) -> Span'Link -> f Span'Link)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> Span'Link
-> f Span'Link
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span'Link -> Text)
-> (Span'Link -> Text -> Span'Link)
-> Lens Span'Link Span'Link Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span'Link -> Text
_Span'Link'traceState
           (\ Span'Link
x__ Text
y__ -> Span'Link
x__ {_Span'Link'traceState :: Text
_Span'Link'traceState = Text
y__}))
        (Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Span'Link "attributes" [Proto.Opentelemetry.Proto.Common.V1.Common.KeyValue] where
  fieldOf :: Proxy# "attributes"
-> ([KeyValue] -> f [KeyValue]) -> Span'Link -> f Span'Link
fieldOf Proxy# "attributes"
_
    = ((Vector KeyValue -> f (Vector KeyValue))
 -> Span'Link -> f Span'Link)
-> (([KeyValue] -> f [KeyValue])
    -> Vector KeyValue -> f (Vector KeyValue))
-> ([KeyValue] -> f [KeyValue])
-> Span'Link
-> f Span'Link
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span'Link -> Vector KeyValue)
-> (Span'Link -> Vector KeyValue -> Span'Link)
-> Lens Span'Link Span'Link (Vector KeyValue) (Vector KeyValue)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span'Link -> Vector KeyValue
_Span'Link'attributes
           (\ Span'Link
x__ Vector KeyValue
y__ -> Span'Link
x__ {_Span'Link'attributes :: Vector KeyValue
_Span'Link'attributes = Vector KeyValue
y__}))
        ((Vector KeyValue -> [KeyValue])
-> (Vector KeyValue -> [KeyValue] -> Vector KeyValue)
-> Lens (Vector KeyValue) (Vector KeyValue) [KeyValue] [KeyValue]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Vector KeyValue -> [KeyValue]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
           (\ Vector KeyValue
_ [KeyValue]
y__ -> [KeyValue] -> Vector KeyValue
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [KeyValue]
y__))
instance Data.ProtoLens.Field.HasField Span'Link "vec'attributes" (Data.Vector.Vector Proto.Opentelemetry.Proto.Common.V1.Common.KeyValue) where
  fieldOf :: Proxy# "vec'attributes"
-> (Vector KeyValue -> f (Vector KeyValue))
-> Span'Link
-> f Span'Link
fieldOf Proxy# "vec'attributes"
_
    = ((Vector KeyValue -> f (Vector KeyValue))
 -> Span'Link -> f Span'Link)
-> ((Vector KeyValue -> f (Vector KeyValue))
    -> Vector KeyValue -> f (Vector KeyValue))
-> (Vector KeyValue -> f (Vector KeyValue))
-> Span'Link
-> f Span'Link
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span'Link -> Vector KeyValue)
-> (Span'Link -> Vector KeyValue -> Span'Link)
-> Lens Span'Link Span'Link (Vector KeyValue) (Vector KeyValue)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span'Link -> Vector KeyValue
_Span'Link'attributes
           (\ Span'Link
x__ Vector KeyValue
y__ -> Span'Link
x__ {_Span'Link'attributes :: Vector KeyValue
_Span'Link'attributes = Vector KeyValue
y__}))
        (Vector KeyValue -> f (Vector KeyValue))
-> Vector KeyValue -> f (Vector KeyValue)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Span'Link "droppedAttributesCount" Data.Word.Word32 where
  fieldOf :: Proxy# "droppedAttributesCount"
-> (Word32 -> f Word32) -> Span'Link -> f Span'Link
fieldOf Proxy# "droppedAttributesCount"
_
    = ((Word32 -> f Word32) -> Span'Link -> f Span'Link)
-> ((Word32 -> f Word32) -> Word32 -> f Word32)
-> (Word32 -> f Word32)
-> Span'Link
-> f Span'Link
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Span'Link -> Word32)
-> (Span'Link -> Word32 -> Span'Link)
-> Lens Span'Link Span'Link Word32 Word32
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Span'Link -> Word32
_Span'Link'droppedAttributesCount
           (\ Span'Link
x__ Word32
y__ -> Span'Link
x__ {_Span'Link'droppedAttributesCount :: Word32
_Span'Link'droppedAttributesCount = Word32
y__}))
        (Word32 -> f Word32) -> Word32 -> f Word32
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message Span'Link where
  messageName :: Proxy Span'Link -> Text
messageName Proxy Span'Link
_
    = String -> Text
Data.Text.pack String
"opentelemetry.proto.trace.v1.Span.Link"
  packedMessageDescriptor :: Proxy Span'Link -> ByteString
packedMessageDescriptor Proxy Span'Link
_
    = ByteString
"\n\
      \\EOTLink\DC2\EM\n\
      \\btrace_id\CAN\SOH \SOH(\fR\atraceId\DC2\ETB\n\
      \\aspan_id\CAN\STX \SOH(\fR\ACKspanId\DC2\US\n\
      \\vtrace_state\CAN\ETX \SOH(\tR\n\
      \traceState\DC2G\n\
      \\n\
      \attributes\CAN\EOT \ETX(\v2'.opentelemetry.proto.common.v1.KeyValueR\n\
      \attributes\DC28\n\
      \\CANdropped_attributes_count\CAN\ENQ \SOH(\rR\SYNdroppedAttributesCount"
  packedFileDescriptor :: Proxy Span'Link -> ByteString
packedFileDescriptor Proxy Span'Link
_ = ByteString
packedFileDescriptor
  fieldsByTag :: Map Tag (FieldDescriptor Span'Link)
fieldsByTag
    = let
        traceId__field_descriptor :: FieldDescriptor Span'Link
traceId__field_descriptor
          = String
-> FieldTypeDescriptor ByteString
-> FieldAccessor Span'Link ByteString
-> FieldDescriptor Span'Link
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"trace_id"
              (ScalarField ByteString -> FieldTypeDescriptor ByteString
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ByteString
Data.ProtoLens.BytesField ::
                 Data.ProtoLens.FieldTypeDescriptor Data.ByteString.ByteString)
              (WireDefault ByteString
-> Lens Span'Link Span'Link ByteString ByteString
-> FieldAccessor Span'Link ByteString
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault ByteString
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional (forall s a (f :: * -> *).
(HasField s "traceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"traceId")) ::
              Data.ProtoLens.FieldDescriptor Span'Link
        spanId__field_descriptor :: FieldDescriptor Span'Link
spanId__field_descriptor
          = String
-> FieldTypeDescriptor ByteString
-> FieldAccessor Span'Link ByteString
-> FieldDescriptor Span'Link
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"span_id"
              (ScalarField ByteString -> FieldTypeDescriptor ByteString
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField ByteString
Data.ProtoLens.BytesField ::
                 Data.ProtoLens.FieldTypeDescriptor Data.ByteString.ByteString)
              (WireDefault ByteString
-> Lens Span'Link Span'Link ByteString ByteString
-> FieldAccessor Span'Link ByteString
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault ByteString
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional (forall s a (f :: * -> *).
(HasField s "spanId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"spanId")) ::
              Data.ProtoLens.FieldDescriptor Span'Link
        traceState__field_descriptor :: FieldDescriptor Span'Link
traceState__field_descriptor
          = String
-> FieldTypeDescriptor Text
-> FieldAccessor Span'Link Text
-> FieldDescriptor Span'Link
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"trace_state"
              (ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
                 Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
              (WireDefault Text
-> Lens Span'Link Span'Link Text Text
-> FieldAccessor Span'Link Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault Text
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional
                 (forall s a (f :: * -> *).
(HasField s "traceState" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"traceState")) ::
              Data.ProtoLens.FieldDescriptor Span'Link
        attributes__field_descriptor :: FieldDescriptor Span'Link
attributes__field_descriptor
          = String
-> FieldTypeDescriptor KeyValue
-> FieldAccessor Span'Link KeyValue
-> FieldDescriptor Span'Link
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"attributes"
              (MessageOrGroup -> FieldTypeDescriptor KeyValue
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
                 Data.ProtoLens.FieldTypeDescriptor Proto.Opentelemetry.Proto.Common.V1.Common.KeyValue)
              (Packing
-> Lens' Span'Link [KeyValue] -> FieldAccessor Span'Link KeyValue
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
                 Packing
Data.ProtoLens.Unpacked
                 (forall s a (f :: * -> *).
(HasField s "attributes" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"attributes")) ::
              Data.ProtoLens.FieldDescriptor Span'Link
        droppedAttributesCount__field_descriptor :: FieldDescriptor Span'Link
droppedAttributesCount__field_descriptor
          = String
-> FieldTypeDescriptor Word32
-> FieldAccessor Span'Link Word32
-> FieldDescriptor Span'Link
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"dropped_attributes_count"
              (ScalarField Word32 -> FieldTypeDescriptor Word32
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Word32
Data.ProtoLens.UInt32Field ::
                 Data.ProtoLens.FieldTypeDescriptor Data.Word.Word32)
              (WireDefault Word32
-> Lens Span'Link Span'Link Word32 Word32
-> FieldAccessor Span'Link Word32
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault Word32
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional
                 (forall s a (f :: * -> *).
(HasField s "droppedAttributesCount" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"droppedAttributesCount")) ::
              Data.ProtoLens.FieldDescriptor Span'Link
      in
        [(Tag, FieldDescriptor Span'Link)]
-> Map Tag (FieldDescriptor Span'Link)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
          [(Int -> Tag
Data.ProtoLens.Tag Int
1, FieldDescriptor Span'Link
traceId__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
2, FieldDescriptor Span'Link
spanId__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
3, FieldDescriptor Span'Link
traceState__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
4, FieldDescriptor Span'Link
attributes__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
5, FieldDescriptor Span'Link
droppedAttributesCount__field_descriptor)]
  unknownFields :: LensLike' f Span'Link FieldSet
unknownFields
    = (Span'Link -> FieldSet)
-> (Span'Link -> FieldSet -> Span'Link) -> Lens' Span'Link FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
        Span'Link -> FieldSet
_Span'Link'_unknownFields
        (\ Span'Link
x__ FieldSet
y__ -> Span'Link
x__ {_Span'Link'_unknownFields :: FieldSet
_Span'Link'_unknownFields = FieldSet
y__})
  defMessage :: Span'Link
defMessage
    = Span'Link'_constructor :: ByteString
-> ByteString
-> Text
-> Vector KeyValue
-> Word32
-> FieldSet
-> Span'Link
Span'Link'_constructor
        {_Span'Link'traceId :: ByteString
_Span'Link'traceId = ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _Span'Link'spanId :: ByteString
_Span'Link'spanId = ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _Span'Link'traceState :: Text
_Span'Link'traceState = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _Span'Link'attributes :: Vector KeyValue
_Span'Link'attributes = Vector KeyValue
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
         _Span'Link'droppedAttributesCount :: Word32
_Span'Link'droppedAttributesCount = Word32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _Span'Link'_unknownFields :: FieldSet
_Span'Link'_unknownFields = []}
  parseMessage :: Parser Span'Link
parseMessage
    = let
        loop ::
          Span'Link
          -> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld Proto.Opentelemetry.Proto.Common.V1.Common.KeyValue
             -> Data.ProtoLens.Encoding.Bytes.Parser Span'Link
        loop :: Span'Link -> Growing Vector RealWorld KeyValue -> Parser Span'Link
loop Span'Link
x Growing Vector RealWorld KeyValue
mutable'attributes
          = do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
               if Bool
end then
                   do Vector KeyValue
frozen'attributes <- IO (Vector KeyValue) -> Parser (Vector KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                             (Growing Vector (PrimState IO) KeyValue -> IO (Vector KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
                                                Growing Vector RealWorld KeyValue
Growing Vector (PrimState IO) KeyValue
mutable'attributes)
                      (let missing :: [a]
missing = []
                       in
                         if [Any] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [Any]
forall a. [a]
missing then
                             () -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
                         else
                             String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
                               (String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
                                  String
"Missing required fields: "
                                  ([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
forall a. [a]
missing :: [Prelude.String]))))
                      Span'Link -> Parser Span'Link
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
                        (Setter Span'Link Span'Link FieldSet FieldSet
-> (FieldSet -> FieldSet) -> Span'Link -> Span'Link
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
                           forall msg. Message msg => Lens' msg FieldSet
Setter Span'Link Span'Link FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
                           (Setter Span'Link Span'Link (Vector KeyValue) (Vector KeyValue)
-> Vector KeyValue -> Span'Link -> Span'Link
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
                              (forall s a (f :: * -> *).
(HasField s "vec'attributes" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'attributes") Vector KeyValue
frozen'attributes
                              Span'Link
x))
               else
                   do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                      case Word64
tag of
                        Word64
10
                          -> do ByteString
y <- Parser ByteString -> String -> Parser ByteString
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       (do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                           Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
                                             (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len))
                                       String
"trace_id"
                                Span'Link -> Growing Vector RealWorld KeyValue -> Parser Span'Link
loop
                                  (Setter Span'Link Span'Link ByteString ByteString
-> ByteString -> Span'Link -> Span'Link
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "traceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"traceId") ByteString
y Span'Link
x)
                                  Growing Vector RealWorld KeyValue
mutable'attributes
                        Word64
18
                          -> do ByteString
y <- Parser ByteString -> String -> Parser ByteString
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       (do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                           Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
                                             (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len))
                                       String
"span_id"
                                Span'Link -> Growing Vector RealWorld KeyValue -> Parser Span'Link
loop
                                  (Setter Span'Link Span'Link ByteString ByteString
-> ByteString -> Span'Link -> Span'Link
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "spanId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"spanId") ByteString
y Span'Link
x)
                                  Growing Vector RealWorld KeyValue
mutable'attributes
                        Word64
26
                          -> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       (do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                                       Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
                                                         (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
                                           Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
                                             (case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
                                                (Prelude.Left UnicodeException
err)
                                                  -> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
                                                (Prelude.Right Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
                                       String
"trace_state"
                                Span'Link -> Growing Vector RealWorld KeyValue -> Parser Span'Link
loop
                                  (Setter Span'Link Span'Link Text Text
-> Text -> Span'Link -> Span'Link
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "traceState" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"traceState") Text
y Span'Link
x)
                                  Growing Vector RealWorld KeyValue
mutable'attributes
                        Word64
34
                          -> do !KeyValue
y <- Parser KeyValue -> String -> Parser KeyValue
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                        (do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                            Int -> Parser KeyValue -> Parser KeyValue
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
                                              (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
                                              Parser KeyValue
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
                                        String
"attributes"
                                Growing Vector RealWorld KeyValue
v <- IO (Growing Vector RealWorld KeyValue)
-> Parser (Growing Vector RealWorld KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                       (Growing Vector (PrimState IO) KeyValue
-> KeyValue -> IO (Growing Vector (PrimState IO) KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append Growing Vector RealWorld KeyValue
Growing Vector (PrimState IO) KeyValue
mutable'attributes KeyValue
y)
                                Span'Link -> Growing Vector RealWorld KeyValue -> Parser Span'Link
loop Span'Link
x Growing Vector RealWorld KeyValue
v
                        Word64
40
                          -> do Word32
y <- Parser Word32 -> String -> Parser Word32
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       ((Word64 -> Word32) -> Parser Word64 -> Parser Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
                                          Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
                                          Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt)
                                       String
"dropped_attributes_count"
                                Span'Link -> Growing Vector RealWorld KeyValue -> Parser Span'Link
loop
                                  (Setter Span'Link Span'Link Word32 Word32
-> Word32 -> Span'Link -> Span'Link
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
                                     (forall s a (f :: * -> *).
(HasField s "droppedAttributesCount" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"droppedAttributesCount") Word32
y Span'Link
x)
                                  Growing Vector RealWorld KeyValue
mutable'attributes
                        Word64
wire
                          -> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
                                        Word64
wire
                                Span'Link -> Growing Vector RealWorld KeyValue -> Parser Span'Link
loop
                                  (Setter Span'Link Span'Link FieldSet FieldSet
-> (FieldSet -> FieldSet) -> Span'Link -> Span'Link
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
                                     forall msg. Message msg => Lens' msg FieldSet
Setter Span'Link Span'Link FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) Span'Link
x)
                                  Growing Vector RealWorld KeyValue
mutable'attributes
      in
        Parser Span'Link -> String -> Parser Span'Link
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
          (do Growing Vector RealWorld KeyValue
mutable'attributes <- IO (Growing Vector RealWorld KeyValue)
-> Parser (Growing Vector RealWorld KeyValue)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                      IO (Growing Vector RealWorld KeyValue)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
              Span'Link -> Growing Vector RealWorld KeyValue -> Parser Span'Link
loop Span'Link
forall msg. Message msg => msg
Data.ProtoLens.defMessage Growing Vector RealWorld KeyValue
mutable'attributes)
          String
"Link"
  buildMessage :: Span'Link -> Builder
buildMessage
    = \ Span'Link
_x
        -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
             (let
                _v :: ByteString
_v = FoldLike ByteString Span'Link Span'Link ByteString ByteString
-> Span'Link -> ByteString
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "traceId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"traceId") Span'Link
_x
              in
                if ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) ByteString
_v ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                    Builder
forall a. Monoid a => a
Data.Monoid.mempty
                else
                    Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                      (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
10)
                      ((\ ByteString
bs
                          -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                               (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                  (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
                               (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
                         ByteString
_v))
             (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                (let
                   _v :: ByteString
_v = FoldLike ByteString Span'Link Span'Link ByteString ByteString
-> Span'Link -> ByteString
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "spanId" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"spanId") Span'Link
_x
                 in
                   if ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) ByteString
_v ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                       Builder
forall a. Monoid a => a
Data.Monoid.mempty
                   else
                       Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                         (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
18)
                         ((\ ByteString
bs
                             -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                  (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                     (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
                                  (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
                            ByteString
_v))
                (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                   (let
                      _v :: Text
_v
                        = FoldLike Text Span'Link Span'Link Text Text -> Span'Link -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "traceState" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"traceState") Span'Link
_x
                    in
                      if Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) Text
_v Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                          Builder
forall a. Monoid a => a
Data.Monoid.mempty
                      else
                          Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                            (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
26)
                            ((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                               (\ ByteString
bs
                                  -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                       (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                          (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
                                       (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
                               Text -> ByteString
Data.Text.Encoding.encodeUtf8 Text
_v))
                   (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                      ((KeyValue -> Builder) -> Vector KeyValue -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
                         (\ KeyValue
_v
                            -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                 (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
34)
                                 ((ByteString -> Builder)
-> (KeyValue -> ByteString) -> KeyValue -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                                    (\ ByteString
bs
                                       -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                            (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                               (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
                                            (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
                                    KeyValue -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage KeyValue
_v))
                         (FoldLike
  (Vector KeyValue)
  Span'Link
  Span'Link
  (Vector KeyValue)
  (Vector KeyValue)
-> Span'Link -> Vector KeyValue
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
                            (forall s a (f :: * -> *).
(HasField s "vec'attributes" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'attributes") Span'Link
_x))
                      (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                         (let
                            _v :: Word32
_v
                              = FoldLike Word32 Span'Link Span'Link Word32 Word32
-> Span'Link -> Word32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
                                  (forall s a (f :: * -> *).
(HasField s "droppedAttributesCount" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"droppedAttributesCount") Span'Link
_x
                          in
                            if Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) Word32
_v Word32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                                Builder
forall a. Monoid a => a
Data.Monoid.mempty
                            else
                                Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                  (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
40)
                                  ((Word64 -> Builder) -> (Word32 -> Word64) -> Word32 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                                     Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
                                     Word32
_v))
                         (FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
                            (FoldLike FieldSet Span'Link Span'Link FieldSet FieldSet
-> Span'Link -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet Span'Link Span'Link FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields Span'Link
_x))))))
instance Control.DeepSeq.NFData Span'Link where
  rnf :: Span'Link -> ()
rnf
    = \ Span'Link
x__
        -> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
             (Span'Link -> FieldSet
_Span'Link'_unknownFields Span'Link
x__)
             (ByteString -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                (Span'Link -> ByteString
_Span'Link'traceId Span'Link
x__)
                (ByteString -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                   (Span'Link -> ByteString
_Span'Link'spanId Span'Link
x__)
                   (Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                      (Span'Link -> Text
_Span'Link'traceState Span'Link
x__)
                      (Vector KeyValue -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                         (Span'Link -> Vector KeyValue
_Span'Link'attributes Span'Link
x__)
                         (Word32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                            (Span'Link -> Word32
_Span'Link'droppedAttributesCount Span'Link
x__) ())))))
newtype Span'SpanKind'UnrecognizedValue
  = Span'SpanKind'UnrecognizedValue Data.Int.Int32
  deriving stock (Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue -> Bool
(Span'SpanKind'UnrecognizedValue
 -> Span'SpanKind'UnrecognizedValue -> Bool)
-> (Span'SpanKind'UnrecognizedValue
    -> Span'SpanKind'UnrecognizedValue -> Bool)
-> Eq Span'SpanKind'UnrecognizedValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue -> Bool
$c/= :: Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue -> Bool
== :: Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue -> Bool
$c== :: Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue -> Bool
Prelude.Eq, Eq Span'SpanKind'UnrecognizedValue
Eq Span'SpanKind'UnrecognizedValue
-> (Span'SpanKind'UnrecognizedValue
    -> Span'SpanKind'UnrecognizedValue -> Ordering)
-> (Span'SpanKind'UnrecognizedValue
    -> Span'SpanKind'UnrecognizedValue -> Bool)
-> (Span'SpanKind'UnrecognizedValue
    -> Span'SpanKind'UnrecognizedValue -> Bool)
-> (Span'SpanKind'UnrecognizedValue
    -> Span'SpanKind'UnrecognizedValue -> Bool)
-> (Span'SpanKind'UnrecognizedValue
    -> Span'SpanKind'UnrecognizedValue -> Bool)
-> (Span'SpanKind'UnrecognizedValue
    -> Span'SpanKind'UnrecognizedValue
    -> Span'SpanKind'UnrecognizedValue)
-> (Span'SpanKind'UnrecognizedValue
    -> Span'SpanKind'UnrecognizedValue
    -> Span'SpanKind'UnrecognizedValue)
-> Ord Span'SpanKind'UnrecognizedValue
Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue -> Bool
Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue -> Ordering
Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue
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 :: Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue
$cmin :: Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue
max :: Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue
$cmax :: Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue
>= :: Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue -> Bool
$c>= :: Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue -> Bool
> :: Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue -> Bool
$c> :: Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue -> Bool
<= :: Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue -> Bool
$c<= :: Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue -> Bool
< :: Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue -> Bool
$c< :: Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue -> Bool
compare :: Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue -> Ordering
$ccompare :: Span'SpanKind'UnrecognizedValue
-> Span'SpanKind'UnrecognizedValue -> Ordering
$cp1Ord :: Eq Span'SpanKind'UnrecognizedValue
Prelude.Ord, Int -> Span'SpanKind'UnrecognizedValue -> ShowS
[Span'SpanKind'UnrecognizedValue] -> ShowS
Span'SpanKind'UnrecognizedValue -> String
(Int -> Span'SpanKind'UnrecognizedValue -> ShowS)
-> (Span'SpanKind'UnrecognizedValue -> String)
-> ([Span'SpanKind'UnrecognizedValue] -> ShowS)
-> Show Span'SpanKind'UnrecognizedValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Span'SpanKind'UnrecognizedValue] -> ShowS
$cshowList :: [Span'SpanKind'UnrecognizedValue] -> ShowS
show :: Span'SpanKind'UnrecognizedValue -> String
$cshow :: Span'SpanKind'UnrecognizedValue -> String
showsPrec :: Int -> Span'SpanKind'UnrecognizedValue -> ShowS
$cshowsPrec :: Int -> Span'SpanKind'UnrecognizedValue -> ShowS
Prelude.Show)
data Span'SpanKind
  = Span'SPAN_KIND_UNSPECIFIED |
    Span'SPAN_KIND_INTERNAL |
    Span'SPAN_KIND_SERVER |
    Span'SPAN_KIND_CLIENT |
    Span'SPAN_KIND_PRODUCER |
    Span'SPAN_KIND_CONSUMER |
    Span'SpanKind'Unrecognized !Span'SpanKind'UnrecognizedValue
  deriving stock (Int -> Span'SpanKind -> ShowS
[Span'SpanKind] -> ShowS
Span'SpanKind -> String
(Int -> Span'SpanKind -> ShowS)
-> (Span'SpanKind -> String)
-> ([Span'SpanKind] -> ShowS)
-> Show Span'SpanKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Span'SpanKind] -> ShowS
$cshowList :: [Span'SpanKind] -> ShowS
show :: Span'SpanKind -> String
$cshow :: Span'SpanKind -> String
showsPrec :: Int -> Span'SpanKind -> ShowS
$cshowsPrec :: Int -> Span'SpanKind -> ShowS
Prelude.Show, Span'SpanKind -> Span'SpanKind -> Bool
(Span'SpanKind -> Span'SpanKind -> Bool)
-> (Span'SpanKind -> Span'SpanKind -> Bool) -> Eq Span'SpanKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Span'SpanKind -> Span'SpanKind -> Bool
$c/= :: Span'SpanKind -> Span'SpanKind -> Bool
== :: Span'SpanKind -> Span'SpanKind -> Bool
$c== :: Span'SpanKind -> Span'SpanKind -> Bool
Prelude.Eq, Eq Span'SpanKind
Eq Span'SpanKind
-> (Span'SpanKind -> Span'SpanKind -> Ordering)
-> (Span'SpanKind -> Span'SpanKind -> Bool)
-> (Span'SpanKind -> Span'SpanKind -> Bool)
-> (Span'SpanKind -> Span'SpanKind -> Bool)
-> (Span'SpanKind -> Span'SpanKind -> Bool)
-> (Span'SpanKind -> Span'SpanKind -> Span'SpanKind)
-> (Span'SpanKind -> Span'SpanKind -> Span'SpanKind)
-> Ord Span'SpanKind
Span'SpanKind -> Span'SpanKind -> Bool
Span'SpanKind -> Span'SpanKind -> Ordering
Span'SpanKind -> Span'SpanKind -> Span'SpanKind
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 :: Span'SpanKind -> Span'SpanKind -> Span'SpanKind
$cmin :: Span'SpanKind -> Span'SpanKind -> Span'SpanKind
max :: Span'SpanKind -> Span'SpanKind -> Span'SpanKind
$cmax :: Span'SpanKind -> Span'SpanKind -> Span'SpanKind
>= :: Span'SpanKind -> Span'SpanKind -> Bool
$c>= :: Span'SpanKind -> Span'SpanKind -> Bool
> :: Span'SpanKind -> Span'SpanKind -> Bool
$c> :: Span'SpanKind -> Span'SpanKind -> Bool
<= :: Span'SpanKind -> Span'SpanKind -> Bool
$c<= :: Span'SpanKind -> Span'SpanKind -> Bool
< :: Span'SpanKind -> Span'SpanKind -> Bool
$c< :: Span'SpanKind -> Span'SpanKind -> Bool
compare :: Span'SpanKind -> Span'SpanKind -> Ordering
$ccompare :: Span'SpanKind -> Span'SpanKind -> Ordering
$cp1Ord :: Eq Span'SpanKind
Prelude.Ord)
instance Data.ProtoLens.MessageEnum Span'SpanKind where
  maybeToEnum :: Int -> Maybe Span'SpanKind
maybeToEnum Int
0 = Span'SpanKind -> Maybe Span'SpanKind
forall a. a -> Maybe a
Prelude.Just Span'SpanKind
Span'SPAN_KIND_UNSPECIFIED
  maybeToEnum Int
1 = Span'SpanKind -> Maybe Span'SpanKind
forall a. a -> Maybe a
Prelude.Just Span'SpanKind
Span'SPAN_KIND_INTERNAL
  maybeToEnum Int
2 = Span'SpanKind -> Maybe Span'SpanKind
forall a. a -> Maybe a
Prelude.Just Span'SpanKind
Span'SPAN_KIND_SERVER
  maybeToEnum Int
3 = Span'SpanKind -> Maybe Span'SpanKind
forall a. a -> Maybe a
Prelude.Just Span'SpanKind
Span'SPAN_KIND_CLIENT
  maybeToEnum Int
4 = Span'SpanKind -> Maybe Span'SpanKind
forall a. a -> Maybe a
Prelude.Just Span'SpanKind
Span'SPAN_KIND_PRODUCER
  maybeToEnum Int
5 = Span'SpanKind -> Maybe Span'SpanKind
forall a. a -> Maybe a
Prelude.Just Span'SpanKind
Span'SPAN_KIND_CONSUMER
  maybeToEnum Int
k
    = Span'SpanKind -> Maybe Span'SpanKind
forall a. a -> Maybe a
Prelude.Just
        (Span'SpanKind'UnrecognizedValue -> Span'SpanKind
Span'SpanKind'Unrecognized
           (Int32 -> Span'SpanKind'UnrecognizedValue
Span'SpanKind'UnrecognizedValue (Int -> Int32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Int
k)))
  showEnum :: Span'SpanKind -> String
showEnum Span'SpanKind
Span'SPAN_KIND_UNSPECIFIED = String
"SPAN_KIND_UNSPECIFIED"
  showEnum Span'SpanKind
Span'SPAN_KIND_INTERNAL = String
"SPAN_KIND_INTERNAL"
  showEnum Span'SpanKind
Span'SPAN_KIND_SERVER = String
"SPAN_KIND_SERVER"
  showEnum Span'SpanKind
Span'SPAN_KIND_CLIENT = String
"SPAN_KIND_CLIENT"
  showEnum Span'SpanKind
Span'SPAN_KIND_PRODUCER = String
"SPAN_KIND_PRODUCER"
  showEnum Span'SpanKind
Span'SPAN_KIND_CONSUMER = String
"SPAN_KIND_CONSUMER"
  showEnum
    (Span'SpanKind'Unrecognized (Span'SpanKind'UnrecognizedValue Int32
k))
    = Int32 -> String
forall a. Show a => a -> String
Prelude.show Int32
k
  readEnum :: String -> Maybe Span'SpanKind
readEnum String
k
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"SPAN_KIND_UNSPECIFIED"
    = Span'SpanKind -> Maybe Span'SpanKind
forall a. a -> Maybe a
Prelude.Just Span'SpanKind
Span'SPAN_KIND_UNSPECIFIED
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"SPAN_KIND_INTERNAL"
    = Span'SpanKind -> Maybe Span'SpanKind
forall a. a -> Maybe a
Prelude.Just Span'SpanKind
Span'SPAN_KIND_INTERNAL
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"SPAN_KIND_SERVER"
    = Span'SpanKind -> Maybe Span'SpanKind
forall a. a -> Maybe a
Prelude.Just Span'SpanKind
Span'SPAN_KIND_SERVER
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"SPAN_KIND_CLIENT"
    = Span'SpanKind -> Maybe Span'SpanKind
forall a. a -> Maybe a
Prelude.Just Span'SpanKind
Span'SPAN_KIND_CLIENT
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"SPAN_KIND_PRODUCER"
    = Span'SpanKind -> Maybe Span'SpanKind
forall a. a -> Maybe a
Prelude.Just Span'SpanKind
Span'SPAN_KIND_PRODUCER
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"SPAN_KIND_CONSUMER"
    = Span'SpanKind -> Maybe Span'SpanKind
forall a. a -> Maybe a
Prelude.Just Span'SpanKind
Span'SPAN_KIND_CONSUMER
    | Bool
Prelude.otherwise
    = Maybe Int -> (Int -> Maybe Span'SpanKind) -> Maybe Span'SpanKind
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
(Prelude.>>=) (String -> Maybe Int
forall a. Read a => String -> Maybe a
Text.Read.readMaybe String
k) Int -> Maybe Span'SpanKind
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum
instance Prelude.Bounded Span'SpanKind where
  minBound :: Span'SpanKind
minBound = Span'SpanKind
Span'SPAN_KIND_UNSPECIFIED
  maxBound :: Span'SpanKind
maxBound = Span'SpanKind
Span'SPAN_KIND_CONSUMER
instance Prelude.Enum Span'SpanKind where
  toEnum :: Int -> Span'SpanKind
toEnum Int
k__
    = Span'SpanKind
-> (Span'SpanKind -> Span'SpanKind)
-> Maybe Span'SpanKind
-> Span'SpanKind
forall b a. b -> (a -> b) -> Maybe a -> b
Prelude.maybe
        (String -> Span'SpanKind
forall a. HasCallStack => String -> a
Prelude.error
           (String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
              String
"toEnum: unknown value for enum SpanKind: " (Int -> String
forall a. Show a => a -> String
Prelude.show Int
k__)))
        Span'SpanKind -> Span'SpanKind
forall a. a -> a
Prelude.id (Int -> Maybe Span'SpanKind
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum Int
k__)
  fromEnum :: Span'SpanKind -> Int
fromEnum Span'SpanKind
Span'SPAN_KIND_UNSPECIFIED = Int
0
  fromEnum Span'SpanKind
Span'SPAN_KIND_INTERNAL = Int
1
  fromEnum Span'SpanKind
Span'SPAN_KIND_SERVER = Int
2
  fromEnum Span'SpanKind
Span'SPAN_KIND_CLIENT = Int
3
  fromEnum Span'SpanKind
Span'SPAN_KIND_PRODUCER = Int
4
  fromEnum Span'SpanKind
Span'SPAN_KIND_CONSUMER = Int
5
  fromEnum
    (Span'SpanKind'Unrecognized (Span'SpanKind'UnrecognizedValue Int32
k))
    = Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Int32
k
  succ :: Span'SpanKind -> Span'SpanKind
succ Span'SpanKind
Span'SPAN_KIND_CONSUMER
    = String -> Span'SpanKind
forall a. HasCallStack => String -> a
Prelude.error
        String
"Span'SpanKind.succ: bad argument Span'SPAN_KIND_CONSUMER. This value would be out of bounds."
  succ Span'SpanKind
Span'SPAN_KIND_UNSPECIFIED = Span'SpanKind
Span'SPAN_KIND_INTERNAL
  succ Span'SpanKind
Span'SPAN_KIND_INTERNAL = Span'SpanKind
Span'SPAN_KIND_SERVER
  succ Span'SpanKind
Span'SPAN_KIND_SERVER = Span'SpanKind
Span'SPAN_KIND_CLIENT
  succ Span'SpanKind
Span'SPAN_KIND_CLIENT = Span'SpanKind
Span'SPAN_KIND_PRODUCER
  succ Span'SpanKind
Span'SPAN_KIND_PRODUCER = Span'SpanKind
Span'SPAN_KIND_CONSUMER
  succ (Span'SpanKind'Unrecognized Span'SpanKind'UnrecognizedValue
_)
    = String -> Span'SpanKind
forall a. HasCallStack => String -> a
Prelude.error
        String
"Span'SpanKind.succ: bad argument: unrecognized value"
  pred :: Span'SpanKind -> Span'SpanKind
pred Span'SpanKind
Span'SPAN_KIND_UNSPECIFIED
    = String -> Span'SpanKind
forall a. HasCallStack => String -> a
Prelude.error
        String
"Span'SpanKind.pred: bad argument Span'SPAN_KIND_UNSPECIFIED. This value would be out of bounds."
  pred Span'SpanKind
Span'SPAN_KIND_INTERNAL = Span'SpanKind
Span'SPAN_KIND_UNSPECIFIED
  pred Span'SpanKind
Span'SPAN_KIND_SERVER = Span'SpanKind
Span'SPAN_KIND_INTERNAL
  pred Span'SpanKind
Span'SPAN_KIND_CLIENT = Span'SpanKind
Span'SPAN_KIND_SERVER
  pred Span'SpanKind
Span'SPAN_KIND_PRODUCER = Span'SpanKind
Span'SPAN_KIND_CLIENT
  pred Span'SpanKind
Span'SPAN_KIND_CONSUMER = Span'SpanKind
Span'SPAN_KIND_PRODUCER
  pred (Span'SpanKind'Unrecognized Span'SpanKind'UnrecognizedValue
_)
    = String -> Span'SpanKind
forall a. HasCallStack => String -> a
Prelude.error
        String
"Span'SpanKind.pred: bad argument: unrecognized value"
  enumFrom :: Span'SpanKind -> [Span'SpanKind]
enumFrom = Span'SpanKind -> [Span'SpanKind]
forall a. (Enum a, Bounded a) => a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFrom
  enumFromTo :: Span'SpanKind -> Span'SpanKind -> [Span'SpanKind]
enumFromTo = Span'SpanKind -> Span'SpanKind -> [Span'SpanKind]
forall a. Enum a => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromTo
  enumFromThen :: Span'SpanKind -> Span'SpanKind -> [Span'SpanKind]
enumFromThen = Span'SpanKind -> Span'SpanKind -> [Span'SpanKind]
forall a. (Enum a, Bounded a) => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThen
  enumFromThenTo :: Span'SpanKind -> Span'SpanKind -> Span'SpanKind -> [Span'SpanKind]
enumFromThenTo = Span'SpanKind -> Span'SpanKind -> Span'SpanKind -> [Span'SpanKind]
forall a. Enum a => a -> a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThenTo
instance Data.ProtoLens.FieldDefault Span'SpanKind where
  fieldDefault :: Span'SpanKind
fieldDefault = Span'SpanKind
Span'SPAN_KIND_UNSPECIFIED
instance Control.DeepSeq.NFData Span'SpanKind where
  rnf :: Span'SpanKind -> ()
rnf Span'SpanKind
x__ = Span'SpanKind -> () -> ()
Prelude.seq Span'SpanKind
x__ ()
{- | Fields :
     
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.deprecatedCode' @:: Lens' Status Status'DeprecatedStatusCode@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.message' @:: Lens' Status Data.Text.Text@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.code' @:: Lens' Status Status'StatusCode@ -}
data Status
  = Status'_constructor {Status -> Status'DeprecatedStatusCode
_Status'deprecatedCode :: !Status'DeprecatedStatusCode,
                         Status -> Text
_Status'message :: !Data.Text.Text,
                         Status -> Status'StatusCode
_Status'code :: !Status'StatusCode,
                         Status -> FieldSet
_Status'_unknownFields :: !Data.ProtoLens.FieldSet}
  deriving stock (Status -> Status -> Bool
(Status -> Status -> Bool)
-> (Status -> Status -> Bool) -> Eq Status
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Status -> Status -> Bool
$c/= :: Status -> Status -> Bool
== :: Status -> Status -> Bool
$c== :: Status -> Status -> Bool
Prelude.Eq, Eq Status
Eq Status
-> (Status -> Status -> Ordering)
-> (Status -> Status -> Bool)
-> (Status -> Status -> Bool)
-> (Status -> Status -> Bool)
-> (Status -> Status -> Bool)
-> (Status -> Status -> Status)
-> (Status -> Status -> Status)
-> Ord Status
Status -> Status -> Bool
Status -> Status -> Ordering
Status -> Status -> Status
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 :: Status -> Status -> Status
$cmin :: Status -> Status -> Status
max :: Status -> Status -> Status
$cmax :: Status -> Status -> Status
>= :: Status -> Status -> Bool
$c>= :: Status -> Status -> Bool
> :: Status -> Status -> Bool
$c> :: Status -> Status -> Bool
<= :: Status -> Status -> Bool
$c<= :: Status -> Status -> Bool
< :: Status -> Status -> Bool
$c< :: Status -> Status -> Bool
compare :: Status -> Status -> Ordering
$ccompare :: Status -> Status -> Ordering
$cp1Ord :: Eq Status
Prelude.Ord)
instance Prelude.Show Status where
  showsPrec :: Int -> Status -> ShowS
showsPrec Int
_ Status
__x String
__s
    = Char -> ShowS
Prelude.showChar
        Char
'{'
        (String -> ShowS
Prelude.showString
           (Status -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort Status
__x) (Char -> ShowS
Prelude.showChar Char
'}' String
__s))
instance Data.ProtoLens.Field.HasField Status "deprecatedCode" Status'DeprecatedStatusCode where
  fieldOf :: Proxy# "deprecatedCode"
-> (Status'DeprecatedStatusCode -> f Status'DeprecatedStatusCode)
-> Status
-> f Status
fieldOf Proxy# "deprecatedCode"
_
    = ((Status'DeprecatedStatusCode -> f Status'DeprecatedStatusCode)
 -> Status -> f Status)
-> ((Status'DeprecatedStatusCode -> f Status'DeprecatedStatusCode)
    -> Status'DeprecatedStatusCode -> f Status'DeprecatedStatusCode)
-> (Status'DeprecatedStatusCode -> f Status'DeprecatedStatusCode)
-> Status
-> f Status
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Status -> Status'DeprecatedStatusCode)
-> (Status -> Status'DeprecatedStatusCode -> Status)
-> Lens
     Status
     Status
     Status'DeprecatedStatusCode
     Status'DeprecatedStatusCode
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Status -> Status'DeprecatedStatusCode
_Status'deprecatedCode
           (\ Status
x__ Status'DeprecatedStatusCode
y__ -> Status
x__ {_Status'deprecatedCode :: Status'DeprecatedStatusCode
_Status'deprecatedCode = Status'DeprecatedStatusCode
y__}))
        (Status'DeprecatedStatusCode -> f Status'DeprecatedStatusCode)
-> Status'DeprecatedStatusCode -> f Status'DeprecatedStatusCode
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Status "message" Data.Text.Text where
  fieldOf :: Proxy# "message" -> (Text -> f Text) -> Status -> f Status
fieldOf Proxy# "message"
_
    = ((Text -> f Text) -> Status -> f Status)
-> ((Text -> f Text) -> Text -> f Text)
-> (Text -> f Text)
-> Status
-> f Status
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Status -> Text)
-> (Status -> Text -> Status) -> Lens Status Status Text Text
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Status -> Text
_Status'message (\ Status
x__ Text
y__ -> Status
x__ {_Status'message :: Text
_Status'message = Text
y__}))
        (Text -> f Text) -> Text -> f Text
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField Status "code" Status'StatusCode where
  fieldOf :: Proxy# "code"
-> (Status'StatusCode -> f Status'StatusCode) -> Status -> f Status
fieldOf Proxy# "code"
_
    = ((Status'StatusCode -> f Status'StatusCode) -> Status -> f Status)
-> ((Status'StatusCode -> f Status'StatusCode)
    -> Status'StatusCode -> f Status'StatusCode)
-> (Status'StatusCode -> f Status'StatusCode)
-> Status
-> f Status
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((Status -> Status'StatusCode)
-> (Status -> Status'StatusCode -> Status)
-> Lens Status Status Status'StatusCode Status'StatusCode
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Status -> Status'StatusCode
_Status'code (\ Status
x__ Status'StatusCode
y__ -> Status
x__ {_Status'code :: Status'StatusCode
_Status'code = Status'StatusCode
y__}))
        (Status'StatusCode -> f Status'StatusCode)
-> Status'StatusCode -> f Status'StatusCode
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message Status where
  messageName :: Proxy Status -> Text
messageName Proxy Status
_
    = String -> Text
Data.Text.pack String
"opentelemetry.proto.trace.v1.Status"
  packedMessageDescriptor :: Proxy Status -> ByteString
packedMessageDescriptor Proxy Status
_
    = ByteString
"\n\
      \\ACKStatus\DC2f\n\
      \\SIdeprecated_code\CAN\SOH \SOH(\SO29.opentelemetry.proto.trace.v1.Status.DeprecatedStatusCodeR\SOdeprecatedCodeB\STX\CAN\SOH\DC2\CAN\n\
      \\amessage\CAN\STX \SOH(\tR\amessage\DC2C\n\
      \\EOTcode\CAN\ETX \SOH(\SO2/.opentelemetry.proto.trace.v1.Status.StatusCodeR\EOTcode\"\218\ENQ\n\
      \\DC4DeprecatedStatusCode\DC2\GS\n\
      \\EMDEPRECATED_STATUS_CODE_OK\DLE\NUL\DC2$\n\
      \ DEPRECATED_STATUS_CODE_CANCELLED\DLE\SOH\DC2(\n\
      \$DEPRECATED_STATUS_CODE_UNKNOWN_ERROR\DLE\STX\DC2+\n\
      \'DEPRECATED_STATUS_CODE_INVALID_ARGUMENT\DLE\ETX\DC2,\n\
      \(DEPRECATED_STATUS_CODE_DEADLINE_EXCEEDED\DLE\EOT\DC2$\n\
      \ DEPRECATED_STATUS_CODE_NOT_FOUND\DLE\ENQ\DC2)\n\
      \%DEPRECATED_STATUS_CODE_ALREADY_EXISTS\DLE\ACK\DC2,\n\
      \(DEPRECATED_STATUS_CODE_PERMISSION_DENIED\DLE\a\DC2-\n\
      \)DEPRECATED_STATUS_CODE_RESOURCE_EXHAUSTED\DLE\b\DC2.\n\
      \*DEPRECATED_STATUS_CODE_FAILED_PRECONDITION\DLE\t\DC2\"\n\
      \\RSDEPRECATED_STATUS_CODE_ABORTED\DLE\n\
      \\DC2'\n\
      \#DEPRECATED_STATUS_CODE_OUT_OF_RANGE\DLE\v\DC2(\n\
      \$DEPRECATED_STATUS_CODE_UNIMPLEMENTED\DLE\f\DC2)\n\
      \%DEPRECATED_STATUS_CODE_INTERNAL_ERROR\DLE\r\DC2&\n\
      \\"DEPRECATED_STATUS_CODE_UNAVAILABLE\DLE\SO\DC2$\n\
      \ DEPRECATED_STATUS_CODE_DATA_LOSS\DLE\SI\DC2*\n\
      \&DEPRECATED_STATUS_CODE_UNAUTHENTICATED\DLE\DLE\"N\n\
      \\n\
      \StatusCode\DC2\NAK\n\
      \\DC1STATUS_CODE_UNSET\DLE\NUL\DC2\DC2\n\
      \\SOSTATUS_CODE_OK\DLE\SOH\DC2\NAK\n\
      \\DC1STATUS_CODE_ERROR\DLE\STX"
  packedFileDescriptor :: Proxy Status -> ByteString
packedFileDescriptor Proxy Status
_ = ByteString
packedFileDescriptor
  fieldsByTag :: Map Tag (FieldDescriptor Status)
fieldsByTag
    = let
        deprecatedCode__field_descriptor :: FieldDescriptor Status
deprecatedCode__field_descriptor
          = String
-> FieldTypeDescriptor Status'DeprecatedStatusCode
-> FieldAccessor Status Status'DeprecatedStatusCode
-> FieldDescriptor Status
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"deprecated_code"
              (ScalarField Status'DeprecatedStatusCode
-> FieldTypeDescriptor Status'DeprecatedStatusCode
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Status'DeprecatedStatusCode
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
                 Data.ProtoLens.FieldTypeDescriptor Status'DeprecatedStatusCode)
              (WireDefault Status'DeprecatedStatusCode
-> Lens
     Status
     Status
     Status'DeprecatedStatusCode
     Status'DeprecatedStatusCode
-> FieldAccessor Status Status'DeprecatedStatusCode
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault Status'DeprecatedStatusCode
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional
                 (forall s a (f :: * -> *).
(HasField s "deprecatedCode" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"deprecatedCode")) ::
              Data.ProtoLens.FieldDescriptor Status
        message__field_descriptor :: FieldDescriptor Status
message__field_descriptor
          = String
-> FieldTypeDescriptor Text
-> FieldAccessor Status Text
-> FieldDescriptor Status
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"message"
              (ScalarField Text -> FieldTypeDescriptor Text
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Text
Data.ProtoLens.StringField ::
                 Data.ProtoLens.FieldTypeDescriptor Data.Text.Text)
              (WireDefault Text
-> Lens Status Status Text Text -> FieldAccessor Status Text
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault Text
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional (forall s a (f :: * -> *).
(HasField s "message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"message")) ::
              Data.ProtoLens.FieldDescriptor Status
        code__field_descriptor :: FieldDescriptor Status
code__field_descriptor
          = String
-> FieldTypeDescriptor Status'StatusCode
-> FieldAccessor Status Status'StatusCode
-> FieldDescriptor Status
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"code"
              (ScalarField Status'StatusCode
-> FieldTypeDescriptor Status'StatusCode
forall value. ScalarField value -> FieldTypeDescriptor value
Data.ProtoLens.ScalarField ScalarField Status'StatusCode
forall t. MessageEnum t => ScalarField t
Data.ProtoLens.EnumField ::
                 Data.ProtoLens.FieldTypeDescriptor Status'StatusCode)
              (WireDefault Status'StatusCode
-> Lens Status Status Status'StatusCode Status'StatusCode
-> FieldAccessor Status Status'StatusCode
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
                 WireDefault Status'StatusCode
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional (forall s a (f :: * -> *).
(HasField s "code" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"code")) ::
              Data.ProtoLens.FieldDescriptor Status
      in
        [(Tag, FieldDescriptor Status)] -> Map Tag (FieldDescriptor Status)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
          [(Int -> Tag
Data.ProtoLens.Tag Int
1, FieldDescriptor Status
deprecatedCode__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
2, FieldDescriptor Status
message__field_descriptor),
           (Int -> Tag
Data.ProtoLens.Tag Int
3, FieldDescriptor Status
code__field_descriptor)]
  unknownFields :: LensLike' f Status FieldSet
unknownFields
    = (Status -> FieldSet)
-> (Status -> FieldSet -> Status) -> Lens' Status FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
        Status -> FieldSet
_Status'_unknownFields
        (\ Status
x__ FieldSet
y__ -> Status
x__ {_Status'_unknownFields :: FieldSet
_Status'_unknownFields = FieldSet
y__})
  defMessage :: Status
defMessage
    = Status'_constructor :: Status'DeprecatedStatusCode
-> Text -> Status'StatusCode -> FieldSet -> Status
Status'_constructor
        {_Status'deprecatedCode :: Status'DeprecatedStatusCode
_Status'deprecatedCode = Status'DeprecatedStatusCode
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _Status'message :: Text
_Status'message = Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _Status'code :: Status'StatusCode
_Status'code = Status'StatusCode
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
         _Status'_unknownFields :: FieldSet
_Status'_unknownFields = []}
  parseMessage :: Parser Status
parseMessage
    = let
        loop :: Status -> Data.ProtoLens.Encoding.Bytes.Parser Status
        loop :: Status -> Parser Status
loop Status
x
          = do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
               if Bool
end then
                   do (let missing :: [a]
missing = []
                       in
                         if [Any] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [Any]
forall a. [a]
missing then
                             () -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
                         else
                             String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
                               (String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
                                  String
"Missing required fields: "
                                  ([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
forall a. [a]
missing :: [Prelude.String]))))
                      Status -> Parser Status
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
                        (Setter Status Status FieldSet FieldSet
-> (FieldSet -> FieldSet) -> Status -> Status
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
                           forall msg. Message msg => Lens' msg FieldSet
Setter Status Status FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) Status
x)
               else
                   do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                      case Word64
tag of
                        Word64
8 -> do Status'DeprecatedStatusCode
y <- Parser Status'DeprecatedStatusCode
-> String -> Parser Status'DeprecatedStatusCode
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       ((Int -> Status'DeprecatedStatusCode)
-> Parser Int -> Parser Status'DeprecatedStatusCode
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
                                          Int -> Status'DeprecatedStatusCode
forall a. Enum a => Int -> a
Prelude.toEnum
                                          ((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
                                             Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
                                             Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
                                       String
"deprecated_code"
                                Status -> Parser Status
loop
                                  (Setter
  Status
  Status
  Status'DeprecatedStatusCode
  Status'DeprecatedStatusCode
-> Status'DeprecatedStatusCode -> Status -> Status
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
                                     (forall s a (f :: * -> *).
(HasField s "deprecatedCode" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"deprecatedCode") Status'DeprecatedStatusCode
y Status
x)
                        Word64
18
                          -> do Text
y <- Parser Text -> String -> Parser Text
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       (do ByteString
value <- do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                                       Int -> Parser ByteString
Data.ProtoLens.Encoding.Bytes.getBytes
                                                         (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
                                           Either String Text -> Parser Text
forall a. Either String a -> Parser a
Data.ProtoLens.Encoding.Bytes.runEither
                                             (case ByteString -> Either UnicodeException Text
Data.Text.Encoding.decodeUtf8' ByteString
value of
                                                (Prelude.Left UnicodeException
err)
                                                  -> String -> Either String Text
forall a b. a -> Either a b
Prelude.Left (UnicodeException -> String
forall a. Show a => a -> String
Prelude.show UnicodeException
err)
                                                (Prelude.Right Text
r) -> Text -> Either String Text
forall a b. b -> Either a b
Prelude.Right Text
r))
                                       String
"message"
                                Status -> Parser Status
loop (Setter Status Status Text Text -> Text -> Status -> Status
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"message") Text
y Status
x)
                        Word64
24
                          -> do Status'StatusCode
y <- Parser Status'StatusCode -> String -> Parser Status'StatusCode
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                       ((Int -> Status'StatusCode)
-> Parser Int -> Parser Status'StatusCode
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
                                          Int -> Status'StatusCode
forall a. Enum a => Int -> a
Prelude.toEnum
                                          ((Word64 -> Int) -> Parser Word64 -> Parser Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap
                                             Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
                                             Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt))
                                       String
"code"
                                Status -> Parser Status
loop (Setter Status Status Status'StatusCode Status'StatusCode
-> Status'StatusCode -> Status -> Status
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall s a (f :: * -> *).
(HasField s "code" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"code") Status'StatusCode
y Status
x)
                        Word64
wire
                          -> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
                                        Word64
wire
                                Status -> Parser Status
loop
                                  (Setter Status Status FieldSet FieldSet
-> (FieldSet -> FieldSet) -> Status -> Status
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
                                     forall msg. Message msg => Lens' msg FieldSet
Setter Status Status FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) Status
x)
      in
        Parser Status -> String -> Parser Status
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
          (do Status -> Parser Status
loop Status
forall msg. Message msg => msg
Data.ProtoLens.defMessage) String
"Status"
  buildMessage :: Status -> Builder
buildMessage
    = \ Status
_x
        -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
             (let
                _v :: Status'DeprecatedStatusCode
_v
                  = FoldLike
  Status'DeprecatedStatusCode
  Status
  Status
  Status'DeprecatedStatusCode
  Status'DeprecatedStatusCode
-> Status -> Status'DeprecatedStatusCode
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
                      (forall s a (f :: * -> *).
(HasField s "deprecatedCode" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"deprecatedCode") Status
_x
              in
                if Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) Status'DeprecatedStatusCode
_v Status'DeprecatedStatusCode
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                    Builder
forall a. Monoid a => a
Data.Monoid.mempty
                else
                    Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                      (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
8)
                      ((Int -> Builder)
-> (Status'DeprecatedStatusCode -> Int)
-> Status'DeprecatedStatusCode
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                         ((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                            Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
                         Status'DeprecatedStatusCode -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum Status'DeprecatedStatusCode
_v))
             (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                (let
                   _v :: Text
_v = FoldLike Text Status Status Text Text -> Status -> Text
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "message" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"message") Status
_x
                 in
                   if Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) Text
_v Text
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                       Builder
forall a. Monoid a => a
Data.Monoid.mempty
                   else
                       Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                         (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
18)
                         ((ByteString -> Builder) -> (Text -> ByteString) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                            (\ ByteString
bs
                               -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                    (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                       (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
                                    (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
                            Text -> ByteString
Data.Text.Encoding.encodeUtf8 Text
_v))
                (Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                   (let _v :: Status'StatusCode
_v = FoldLike
  Status'StatusCode Status Status Status'StatusCode Status'StatusCode
-> Status -> Status'StatusCode
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall s a (f :: * -> *).
(HasField s "code" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"code") Status
_x
                    in
                      if Status'StatusCode -> Status'StatusCode -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) Status'StatusCode
_v Status'StatusCode
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
                          Builder
forall a. Monoid a => a
Data.Monoid.mempty
                      else
                          Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                            (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
24)
                            ((Int -> Builder)
-> (Status'StatusCode -> Int) -> Status'StatusCode -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                               ((Word64 -> Builder) -> (Int -> Word64) -> Int -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                                  Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral)
                               Status'StatusCode -> Int
forall a. Enum a => a -> Int
Prelude.fromEnum Status'StatusCode
_v))
                   (FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
                      (FoldLike FieldSet Status Status FieldSet FieldSet
-> Status -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet Status Status FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields Status
_x))))
instance Control.DeepSeq.NFData Status where
  rnf :: Status -> ()
rnf
    = \ Status
x__
        -> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
             (Status -> FieldSet
_Status'_unknownFields Status
x__)
             (Status'DeprecatedStatusCode -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                (Status -> Status'DeprecatedStatusCode
_Status'deprecatedCode Status
x__)
                (Text -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
                   (Status -> Text
_Status'message Status
x__)
                   (Status'StatusCode -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (Status -> Status'StatusCode
_Status'code Status
x__) ())))
newtype Status'DeprecatedStatusCode'UnrecognizedValue
  = Status'DeprecatedStatusCode'UnrecognizedValue Data.Int.Int32
  deriving stock (Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue -> Bool
(Status'DeprecatedStatusCode'UnrecognizedValue
 -> Status'DeprecatedStatusCode'UnrecognizedValue -> Bool)
-> (Status'DeprecatedStatusCode'UnrecognizedValue
    -> Status'DeprecatedStatusCode'UnrecognizedValue -> Bool)
-> Eq Status'DeprecatedStatusCode'UnrecognizedValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue -> Bool
$c/= :: Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue -> Bool
== :: Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue -> Bool
$c== :: Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue -> Bool
Prelude.Eq, Eq Status'DeprecatedStatusCode'UnrecognizedValue
Eq Status'DeprecatedStatusCode'UnrecognizedValue
-> (Status'DeprecatedStatusCode'UnrecognizedValue
    -> Status'DeprecatedStatusCode'UnrecognizedValue -> Ordering)
-> (Status'DeprecatedStatusCode'UnrecognizedValue
    -> Status'DeprecatedStatusCode'UnrecognizedValue -> Bool)
-> (Status'DeprecatedStatusCode'UnrecognizedValue
    -> Status'DeprecatedStatusCode'UnrecognizedValue -> Bool)
-> (Status'DeprecatedStatusCode'UnrecognizedValue
    -> Status'DeprecatedStatusCode'UnrecognizedValue -> Bool)
-> (Status'DeprecatedStatusCode'UnrecognizedValue
    -> Status'DeprecatedStatusCode'UnrecognizedValue -> Bool)
-> (Status'DeprecatedStatusCode'UnrecognizedValue
    -> Status'DeprecatedStatusCode'UnrecognizedValue
    -> Status'DeprecatedStatusCode'UnrecognizedValue)
-> (Status'DeprecatedStatusCode'UnrecognizedValue
    -> Status'DeprecatedStatusCode'UnrecognizedValue
    -> Status'DeprecatedStatusCode'UnrecognizedValue)
-> Ord Status'DeprecatedStatusCode'UnrecognizedValue
Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue -> Bool
Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue -> Ordering
Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue
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 :: Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue
$cmin :: Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue
max :: Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue
$cmax :: Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue
>= :: Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue -> Bool
$c>= :: Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue -> Bool
> :: Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue -> Bool
$c> :: Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue -> Bool
<= :: Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue -> Bool
$c<= :: Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue -> Bool
< :: Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue -> Bool
$c< :: Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue -> Bool
compare :: Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue -> Ordering
$ccompare :: Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode'UnrecognizedValue -> Ordering
$cp1Ord :: Eq Status'DeprecatedStatusCode'UnrecognizedValue
Prelude.Ord, Int -> Status'DeprecatedStatusCode'UnrecognizedValue -> ShowS
[Status'DeprecatedStatusCode'UnrecognizedValue] -> ShowS
Status'DeprecatedStatusCode'UnrecognizedValue -> String
(Int -> Status'DeprecatedStatusCode'UnrecognizedValue -> ShowS)
-> (Status'DeprecatedStatusCode'UnrecognizedValue -> String)
-> ([Status'DeprecatedStatusCode'UnrecognizedValue] -> ShowS)
-> Show Status'DeprecatedStatusCode'UnrecognizedValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Status'DeprecatedStatusCode'UnrecognizedValue] -> ShowS
$cshowList :: [Status'DeprecatedStatusCode'UnrecognizedValue] -> ShowS
show :: Status'DeprecatedStatusCode'UnrecognizedValue -> String
$cshow :: Status'DeprecatedStatusCode'UnrecognizedValue -> String
showsPrec :: Int -> Status'DeprecatedStatusCode'UnrecognizedValue -> ShowS
$cshowsPrec :: Int -> Status'DeprecatedStatusCode'UnrecognizedValue -> ShowS
Prelude.Show)
data Status'DeprecatedStatusCode
  = Status'DEPRECATED_STATUS_CODE_OK |
    Status'DEPRECATED_STATUS_CODE_CANCELLED |
    Status'DEPRECATED_STATUS_CODE_UNKNOWN_ERROR |
    Status'DEPRECATED_STATUS_CODE_INVALID_ARGUMENT |
    Status'DEPRECATED_STATUS_CODE_DEADLINE_EXCEEDED |
    Status'DEPRECATED_STATUS_CODE_NOT_FOUND |
    Status'DEPRECATED_STATUS_CODE_ALREADY_EXISTS |
    Status'DEPRECATED_STATUS_CODE_PERMISSION_DENIED |
    Status'DEPRECATED_STATUS_CODE_RESOURCE_EXHAUSTED |
    Status'DEPRECATED_STATUS_CODE_FAILED_PRECONDITION |
    Status'DEPRECATED_STATUS_CODE_ABORTED |
    Status'DEPRECATED_STATUS_CODE_OUT_OF_RANGE |
    Status'DEPRECATED_STATUS_CODE_UNIMPLEMENTED |
    Status'DEPRECATED_STATUS_CODE_INTERNAL_ERROR |
    Status'DEPRECATED_STATUS_CODE_UNAVAILABLE |
    Status'DEPRECATED_STATUS_CODE_DATA_LOSS |
    Status'DEPRECATED_STATUS_CODE_UNAUTHENTICATED |
    Status'DeprecatedStatusCode'Unrecognized !Status'DeprecatedStatusCode'UnrecognizedValue
  deriving stock (Int -> Status'DeprecatedStatusCode -> ShowS
[Status'DeprecatedStatusCode] -> ShowS
Status'DeprecatedStatusCode -> String
(Int -> Status'DeprecatedStatusCode -> ShowS)
-> (Status'DeprecatedStatusCode -> String)
-> ([Status'DeprecatedStatusCode] -> ShowS)
-> Show Status'DeprecatedStatusCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Status'DeprecatedStatusCode] -> ShowS
$cshowList :: [Status'DeprecatedStatusCode] -> ShowS
show :: Status'DeprecatedStatusCode -> String
$cshow :: Status'DeprecatedStatusCode -> String
showsPrec :: Int -> Status'DeprecatedStatusCode -> ShowS
$cshowsPrec :: Int -> Status'DeprecatedStatusCode -> ShowS
Prelude.Show, Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode -> Bool
(Status'DeprecatedStatusCode
 -> Status'DeprecatedStatusCode -> Bool)
-> (Status'DeprecatedStatusCode
    -> Status'DeprecatedStatusCode -> Bool)
-> Eq Status'DeprecatedStatusCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode -> Bool
$c/= :: Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode -> Bool
== :: Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode -> Bool
$c== :: Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode -> Bool
Prelude.Eq, Eq Status'DeprecatedStatusCode
Eq Status'DeprecatedStatusCode
-> (Status'DeprecatedStatusCode
    -> Status'DeprecatedStatusCode -> Ordering)
-> (Status'DeprecatedStatusCode
    -> Status'DeprecatedStatusCode -> Bool)
-> (Status'DeprecatedStatusCode
    -> Status'DeprecatedStatusCode -> Bool)
-> (Status'DeprecatedStatusCode
    -> Status'DeprecatedStatusCode -> Bool)
-> (Status'DeprecatedStatusCode
    -> Status'DeprecatedStatusCode -> Bool)
-> (Status'DeprecatedStatusCode
    -> Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode)
-> (Status'DeprecatedStatusCode
    -> Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode)
-> Ord Status'DeprecatedStatusCode
Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode -> Bool
Status'DeprecatedStatusCode
-> Status'DeprecatedStatusCode -> Ordering
Status'DeprecatedStatusCode
-> Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode
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 :: Status'DeprecatedStatusCode
-> Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode
$cmin :: Status'DeprecatedStatusCode
-> Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode
max :: Status'DeprecatedStatusCode
-> Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode
$cmax :: Status'DeprecatedStatusCode
-> Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode
>= :: Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode -> Bool
$c>= :: Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode -> Bool
> :: Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode -> Bool
$c> :: Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode -> Bool
<= :: Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode -> Bool
$c<= :: Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode -> Bool
< :: Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode -> Bool
$c< :: Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode -> Bool
compare :: Status'DeprecatedStatusCode
-> Status'DeprecatedStatusCode -> Ordering
$ccompare :: Status'DeprecatedStatusCode
-> Status'DeprecatedStatusCode -> Ordering
$cp1Ord :: Eq Status'DeprecatedStatusCode
Prelude.Ord)
instance Data.ProtoLens.MessageEnum Status'DeprecatedStatusCode where
  maybeToEnum :: Int -> Maybe Status'DeprecatedStatusCode
maybeToEnum Int
0 = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_OK
  maybeToEnum Int
1
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_CANCELLED
  maybeToEnum Int
2
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNKNOWN_ERROR
  maybeToEnum Int
3
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_INVALID_ARGUMENT
  maybeToEnum Int
4
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_DEADLINE_EXCEEDED
  maybeToEnum Int
5
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_NOT_FOUND
  maybeToEnum Int
6
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_ALREADY_EXISTS
  maybeToEnum Int
7
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_PERMISSION_DENIED
  maybeToEnum Int
8
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_RESOURCE_EXHAUSTED
  maybeToEnum Int
9
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_FAILED_PRECONDITION
  maybeToEnum Int
10 = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_ABORTED
  maybeToEnum Int
11
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_OUT_OF_RANGE
  maybeToEnum Int
12
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNIMPLEMENTED
  maybeToEnum Int
13
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_INTERNAL_ERROR
  maybeToEnum Int
14
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNAVAILABLE
  maybeToEnum Int
15
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_DATA_LOSS
  maybeToEnum Int
16
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNAUTHENTICATED
  maybeToEnum Int
k
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just
        (Status'DeprecatedStatusCode'UnrecognizedValue
-> Status'DeprecatedStatusCode
Status'DeprecatedStatusCode'Unrecognized
           (Int32 -> Status'DeprecatedStatusCode'UnrecognizedValue
Status'DeprecatedStatusCode'UnrecognizedValue
              (Int -> Int32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Int
k)))
  showEnum :: Status'DeprecatedStatusCode -> String
showEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_OK
    = String
"DEPRECATED_STATUS_CODE_OK"
  showEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_CANCELLED
    = String
"DEPRECATED_STATUS_CODE_CANCELLED"
  showEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNKNOWN_ERROR
    = String
"DEPRECATED_STATUS_CODE_UNKNOWN_ERROR"
  showEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_INVALID_ARGUMENT
    = String
"DEPRECATED_STATUS_CODE_INVALID_ARGUMENT"
  showEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_DEADLINE_EXCEEDED
    = String
"DEPRECATED_STATUS_CODE_DEADLINE_EXCEEDED"
  showEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_NOT_FOUND
    = String
"DEPRECATED_STATUS_CODE_NOT_FOUND"
  showEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_ALREADY_EXISTS
    = String
"DEPRECATED_STATUS_CODE_ALREADY_EXISTS"
  showEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_PERMISSION_DENIED
    = String
"DEPRECATED_STATUS_CODE_PERMISSION_DENIED"
  showEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_RESOURCE_EXHAUSTED
    = String
"DEPRECATED_STATUS_CODE_RESOURCE_EXHAUSTED"
  showEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_FAILED_PRECONDITION
    = String
"DEPRECATED_STATUS_CODE_FAILED_PRECONDITION"
  showEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_ABORTED
    = String
"DEPRECATED_STATUS_CODE_ABORTED"
  showEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_OUT_OF_RANGE
    = String
"DEPRECATED_STATUS_CODE_OUT_OF_RANGE"
  showEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNIMPLEMENTED
    = String
"DEPRECATED_STATUS_CODE_UNIMPLEMENTED"
  showEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_INTERNAL_ERROR
    = String
"DEPRECATED_STATUS_CODE_INTERNAL_ERROR"
  showEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNAVAILABLE
    = String
"DEPRECATED_STATUS_CODE_UNAVAILABLE"
  showEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_DATA_LOSS
    = String
"DEPRECATED_STATUS_CODE_DATA_LOSS"
  showEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNAUTHENTICATED
    = String
"DEPRECATED_STATUS_CODE_UNAUTHENTICATED"
  showEnum
    (Status'DeprecatedStatusCode'Unrecognized (Status'DeprecatedStatusCode'UnrecognizedValue Int32
k))
    = Int32 -> String
forall a. Show a => a -> String
Prelude.show Int32
k
  readEnum :: String -> Maybe Status'DeprecatedStatusCode
readEnum String
k
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"DEPRECATED_STATUS_CODE_OK"
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_OK
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"DEPRECATED_STATUS_CODE_CANCELLED"
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_CANCELLED
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"DEPRECATED_STATUS_CODE_UNKNOWN_ERROR"
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNKNOWN_ERROR
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"DEPRECATED_STATUS_CODE_INVALID_ARGUMENT"
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_INVALID_ARGUMENT
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"DEPRECATED_STATUS_CODE_DEADLINE_EXCEEDED"
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_DEADLINE_EXCEEDED
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"DEPRECATED_STATUS_CODE_NOT_FOUND"
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_NOT_FOUND
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"DEPRECATED_STATUS_CODE_ALREADY_EXISTS"
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_ALREADY_EXISTS
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"DEPRECATED_STATUS_CODE_PERMISSION_DENIED"
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_PERMISSION_DENIED
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"DEPRECATED_STATUS_CODE_RESOURCE_EXHAUSTED"
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_RESOURCE_EXHAUSTED
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"DEPRECATED_STATUS_CODE_FAILED_PRECONDITION"
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_FAILED_PRECONDITION
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"DEPRECATED_STATUS_CODE_ABORTED"
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_ABORTED
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"DEPRECATED_STATUS_CODE_OUT_OF_RANGE"
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_OUT_OF_RANGE
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"DEPRECATED_STATUS_CODE_UNIMPLEMENTED"
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNIMPLEMENTED
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"DEPRECATED_STATUS_CODE_INTERNAL_ERROR"
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_INTERNAL_ERROR
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"DEPRECATED_STATUS_CODE_UNAVAILABLE"
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNAVAILABLE
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"DEPRECATED_STATUS_CODE_DATA_LOSS"
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_DATA_LOSS
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"DEPRECATED_STATUS_CODE_UNAUTHENTICATED"
    = Status'DeprecatedStatusCode -> Maybe Status'DeprecatedStatusCode
forall a. a -> Maybe a
Prelude.Just Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNAUTHENTICATED
    | Bool
Prelude.otherwise
    = Maybe Int
-> (Int -> Maybe Status'DeprecatedStatusCode)
-> Maybe Status'DeprecatedStatusCode
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
(Prelude.>>=) (String -> Maybe Int
forall a. Read a => String -> Maybe a
Text.Read.readMaybe String
k) Int -> Maybe Status'DeprecatedStatusCode
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum
instance Prelude.Bounded Status'DeprecatedStatusCode where
  minBound :: Status'DeprecatedStatusCode
minBound = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_OK
  maxBound :: Status'DeprecatedStatusCode
maxBound = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNAUTHENTICATED
instance Prelude.Enum Status'DeprecatedStatusCode where
  toEnum :: Int -> Status'DeprecatedStatusCode
toEnum Int
k__
    = Status'DeprecatedStatusCode
-> (Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode)
-> Maybe Status'DeprecatedStatusCode
-> Status'DeprecatedStatusCode
forall b a. b -> (a -> b) -> Maybe a -> b
Prelude.maybe
        (String -> Status'DeprecatedStatusCode
forall a. HasCallStack => String -> a
Prelude.error
           (String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
              String
"toEnum: unknown value for enum DeprecatedStatusCode: "
              (Int -> String
forall a. Show a => a -> String
Prelude.show Int
k__)))
        Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode
forall a. a -> a
Prelude.id (Int -> Maybe Status'DeprecatedStatusCode
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum Int
k__)
  fromEnum :: Status'DeprecatedStatusCode -> Int
fromEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_OK = Int
0
  fromEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_CANCELLED = Int
1
  fromEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNKNOWN_ERROR = Int
2
  fromEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_INVALID_ARGUMENT = Int
3
  fromEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_DEADLINE_EXCEEDED = Int
4
  fromEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_NOT_FOUND = Int
5
  fromEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_ALREADY_EXISTS = Int
6
  fromEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_PERMISSION_DENIED = Int
7
  fromEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_RESOURCE_EXHAUSTED = Int
8
  fromEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_FAILED_PRECONDITION = Int
9
  fromEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_ABORTED = Int
10
  fromEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_OUT_OF_RANGE = Int
11
  fromEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNIMPLEMENTED = Int
12
  fromEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_INTERNAL_ERROR = Int
13
  fromEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNAVAILABLE = Int
14
  fromEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_DATA_LOSS = Int
15
  fromEnum Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNAUTHENTICATED = Int
16
  fromEnum
    (Status'DeprecatedStatusCode'Unrecognized (Status'DeprecatedStatusCode'UnrecognizedValue Int32
k))
    = Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Int32
k
  succ :: Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode
succ Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNAUTHENTICATED
    = String -> Status'DeprecatedStatusCode
forall a. HasCallStack => String -> a
Prelude.error
        String
"Status'DeprecatedStatusCode.succ: bad argument Status'DEPRECATED_STATUS_CODE_UNAUTHENTICATED. This value would be out of bounds."
  succ Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_OK
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_CANCELLED
  succ Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_CANCELLED
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNKNOWN_ERROR
  succ Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNKNOWN_ERROR
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_INVALID_ARGUMENT
  succ Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_INVALID_ARGUMENT
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_DEADLINE_EXCEEDED
  succ Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_DEADLINE_EXCEEDED
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_NOT_FOUND
  succ Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_NOT_FOUND
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_ALREADY_EXISTS
  succ Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_ALREADY_EXISTS
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_PERMISSION_DENIED
  succ Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_PERMISSION_DENIED
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_RESOURCE_EXHAUSTED
  succ Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_RESOURCE_EXHAUSTED
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_FAILED_PRECONDITION
  succ Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_FAILED_PRECONDITION
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_ABORTED
  succ Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_ABORTED
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_OUT_OF_RANGE
  succ Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_OUT_OF_RANGE
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNIMPLEMENTED
  succ Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNIMPLEMENTED
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_INTERNAL_ERROR
  succ Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_INTERNAL_ERROR
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNAVAILABLE
  succ Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNAVAILABLE
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_DATA_LOSS
  succ Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_DATA_LOSS
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNAUTHENTICATED
  succ (Status'DeprecatedStatusCode'Unrecognized Status'DeprecatedStatusCode'UnrecognizedValue
_)
    = String -> Status'DeprecatedStatusCode
forall a. HasCallStack => String -> a
Prelude.error
        String
"Status'DeprecatedStatusCode.succ: bad argument: unrecognized value"
  pred :: Status'DeprecatedStatusCode -> Status'DeprecatedStatusCode
pred Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_OK
    = String -> Status'DeprecatedStatusCode
forall a. HasCallStack => String -> a
Prelude.error
        String
"Status'DeprecatedStatusCode.pred: bad argument Status'DEPRECATED_STATUS_CODE_OK. This value would be out of bounds."
  pred Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_CANCELLED
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_OK
  pred Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNKNOWN_ERROR
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_CANCELLED
  pred Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_INVALID_ARGUMENT
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNKNOWN_ERROR
  pred Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_DEADLINE_EXCEEDED
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_INVALID_ARGUMENT
  pred Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_NOT_FOUND
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_DEADLINE_EXCEEDED
  pred Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_ALREADY_EXISTS
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_NOT_FOUND
  pred Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_PERMISSION_DENIED
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_ALREADY_EXISTS
  pred Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_RESOURCE_EXHAUSTED
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_PERMISSION_DENIED
  pred Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_FAILED_PRECONDITION
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_RESOURCE_EXHAUSTED
  pred Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_ABORTED
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_FAILED_PRECONDITION
  pred Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_OUT_OF_RANGE
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_ABORTED
  pred Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNIMPLEMENTED
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_OUT_OF_RANGE
  pred Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_INTERNAL_ERROR
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNIMPLEMENTED
  pred Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNAVAILABLE
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_INTERNAL_ERROR
  pred Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_DATA_LOSS
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNAVAILABLE
  pred Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_UNAUTHENTICATED
    = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_DATA_LOSS
  pred (Status'DeprecatedStatusCode'Unrecognized Status'DeprecatedStatusCode'UnrecognizedValue
_)
    = String -> Status'DeprecatedStatusCode
forall a. HasCallStack => String -> a
Prelude.error
        String
"Status'DeprecatedStatusCode.pred: bad argument: unrecognized value"
  enumFrom :: Status'DeprecatedStatusCode -> [Status'DeprecatedStatusCode]
enumFrom = Status'DeprecatedStatusCode -> [Status'DeprecatedStatusCode]
forall a. (Enum a, Bounded a) => a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFrom
  enumFromTo :: Status'DeprecatedStatusCode
-> Status'DeprecatedStatusCode -> [Status'DeprecatedStatusCode]
enumFromTo = Status'DeprecatedStatusCode
-> Status'DeprecatedStatusCode -> [Status'DeprecatedStatusCode]
forall a. Enum a => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromTo
  enumFromThen :: Status'DeprecatedStatusCode
-> Status'DeprecatedStatusCode -> [Status'DeprecatedStatusCode]
enumFromThen = Status'DeprecatedStatusCode
-> Status'DeprecatedStatusCode -> [Status'DeprecatedStatusCode]
forall a. (Enum a, Bounded a) => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThen
  enumFromThenTo :: Status'DeprecatedStatusCode
-> Status'DeprecatedStatusCode
-> Status'DeprecatedStatusCode
-> [Status'DeprecatedStatusCode]
enumFromThenTo = Status'DeprecatedStatusCode
-> Status'DeprecatedStatusCode
-> Status'DeprecatedStatusCode
-> [Status'DeprecatedStatusCode]
forall a. Enum a => a -> a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThenTo
instance Data.ProtoLens.FieldDefault Status'DeprecatedStatusCode where
  fieldDefault :: Status'DeprecatedStatusCode
fieldDefault = Status'DeprecatedStatusCode
Status'DEPRECATED_STATUS_CODE_OK
instance Control.DeepSeq.NFData Status'DeprecatedStatusCode where
  rnf :: Status'DeprecatedStatusCode -> ()
rnf Status'DeprecatedStatusCode
x__ = Status'DeprecatedStatusCode -> () -> ()
Prelude.seq Status'DeprecatedStatusCode
x__ ()
newtype Status'StatusCode'UnrecognizedValue
  = Status'StatusCode'UnrecognizedValue Data.Int.Int32
  deriving stock (Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue -> Bool
(Status'StatusCode'UnrecognizedValue
 -> Status'StatusCode'UnrecognizedValue -> Bool)
-> (Status'StatusCode'UnrecognizedValue
    -> Status'StatusCode'UnrecognizedValue -> Bool)
-> Eq Status'StatusCode'UnrecognizedValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue -> Bool
$c/= :: Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue -> Bool
== :: Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue -> Bool
$c== :: Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue -> Bool
Prelude.Eq, Eq Status'StatusCode'UnrecognizedValue
Eq Status'StatusCode'UnrecognizedValue
-> (Status'StatusCode'UnrecognizedValue
    -> Status'StatusCode'UnrecognizedValue -> Ordering)
-> (Status'StatusCode'UnrecognizedValue
    -> Status'StatusCode'UnrecognizedValue -> Bool)
-> (Status'StatusCode'UnrecognizedValue
    -> Status'StatusCode'UnrecognizedValue -> Bool)
-> (Status'StatusCode'UnrecognizedValue
    -> Status'StatusCode'UnrecognizedValue -> Bool)
-> (Status'StatusCode'UnrecognizedValue
    -> Status'StatusCode'UnrecognizedValue -> Bool)
-> (Status'StatusCode'UnrecognizedValue
    -> Status'StatusCode'UnrecognizedValue
    -> Status'StatusCode'UnrecognizedValue)
-> (Status'StatusCode'UnrecognizedValue
    -> Status'StatusCode'UnrecognizedValue
    -> Status'StatusCode'UnrecognizedValue)
-> Ord Status'StatusCode'UnrecognizedValue
Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue -> Bool
Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue -> Ordering
Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue
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 :: Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue
$cmin :: Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue
max :: Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue
$cmax :: Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue
>= :: Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue -> Bool
$c>= :: Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue -> Bool
> :: Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue -> Bool
$c> :: Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue -> Bool
<= :: Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue -> Bool
$c<= :: Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue -> Bool
< :: Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue -> Bool
$c< :: Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue -> Bool
compare :: Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue -> Ordering
$ccompare :: Status'StatusCode'UnrecognizedValue
-> Status'StatusCode'UnrecognizedValue -> Ordering
$cp1Ord :: Eq Status'StatusCode'UnrecognizedValue
Prelude.Ord, Int -> Status'StatusCode'UnrecognizedValue -> ShowS
[Status'StatusCode'UnrecognizedValue] -> ShowS
Status'StatusCode'UnrecognizedValue -> String
(Int -> Status'StatusCode'UnrecognizedValue -> ShowS)
-> (Status'StatusCode'UnrecognizedValue -> String)
-> ([Status'StatusCode'UnrecognizedValue] -> ShowS)
-> Show Status'StatusCode'UnrecognizedValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Status'StatusCode'UnrecognizedValue] -> ShowS
$cshowList :: [Status'StatusCode'UnrecognizedValue] -> ShowS
show :: Status'StatusCode'UnrecognizedValue -> String
$cshow :: Status'StatusCode'UnrecognizedValue -> String
showsPrec :: Int -> Status'StatusCode'UnrecognizedValue -> ShowS
$cshowsPrec :: Int -> Status'StatusCode'UnrecognizedValue -> ShowS
Prelude.Show)
data Status'StatusCode
  = Status'STATUS_CODE_UNSET |
    Status'STATUS_CODE_OK |
    Status'STATUS_CODE_ERROR |
    Status'StatusCode'Unrecognized !Status'StatusCode'UnrecognizedValue
  deriving stock (Int -> Status'StatusCode -> ShowS
[Status'StatusCode] -> ShowS
Status'StatusCode -> String
(Int -> Status'StatusCode -> ShowS)
-> (Status'StatusCode -> String)
-> ([Status'StatusCode] -> ShowS)
-> Show Status'StatusCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Status'StatusCode] -> ShowS
$cshowList :: [Status'StatusCode] -> ShowS
show :: Status'StatusCode -> String
$cshow :: Status'StatusCode -> String
showsPrec :: Int -> Status'StatusCode -> ShowS
$cshowsPrec :: Int -> Status'StatusCode -> ShowS
Prelude.Show, Status'StatusCode -> Status'StatusCode -> Bool
(Status'StatusCode -> Status'StatusCode -> Bool)
-> (Status'StatusCode -> Status'StatusCode -> Bool)
-> Eq Status'StatusCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Status'StatusCode -> Status'StatusCode -> Bool
$c/= :: Status'StatusCode -> Status'StatusCode -> Bool
== :: Status'StatusCode -> Status'StatusCode -> Bool
$c== :: Status'StatusCode -> Status'StatusCode -> Bool
Prelude.Eq, Eq Status'StatusCode
Eq Status'StatusCode
-> (Status'StatusCode -> Status'StatusCode -> Ordering)
-> (Status'StatusCode -> Status'StatusCode -> Bool)
-> (Status'StatusCode -> Status'StatusCode -> Bool)
-> (Status'StatusCode -> Status'StatusCode -> Bool)
-> (Status'StatusCode -> Status'StatusCode -> Bool)
-> (Status'StatusCode -> Status'StatusCode -> Status'StatusCode)
-> (Status'StatusCode -> Status'StatusCode -> Status'StatusCode)
-> Ord Status'StatusCode
Status'StatusCode -> Status'StatusCode -> Bool
Status'StatusCode -> Status'StatusCode -> Ordering
Status'StatusCode -> Status'StatusCode -> Status'StatusCode
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 :: Status'StatusCode -> Status'StatusCode -> Status'StatusCode
$cmin :: Status'StatusCode -> Status'StatusCode -> Status'StatusCode
max :: Status'StatusCode -> Status'StatusCode -> Status'StatusCode
$cmax :: Status'StatusCode -> Status'StatusCode -> Status'StatusCode
>= :: Status'StatusCode -> Status'StatusCode -> Bool
$c>= :: Status'StatusCode -> Status'StatusCode -> Bool
> :: Status'StatusCode -> Status'StatusCode -> Bool
$c> :: Status'StatusCode -> Status'StatusCode -> Bool
<= :: Status'StatusCode -> Status'StatusCode -> Bool
$c<= :: Status'StatusCode -> Status'StatusCode -> Bool
< :: Status'StatusCode -> Status'StatusCode -> Bool
$c< :: Status'StatusCode -> Status'StatusCode -> Bool
compare :: Status'StatusCode -> Status'StatusCode -> Ordering
$ccompare :: Status'StatusCode -> Status'StatusCode -> Ordering
$cp1Ord :: Eq Status'StatusCode
Prelude.Ord)
instance Data.ProtoLens.MessageEnum Status'StatusCode where
  maybeToEnum :: Int -> Maybe Status'StatusCode
maybeToEnum Int
0 = Status'StatusCode -> Maybe Status'StatusCode
forall a. a -> Maybe a
Prelude.Just Status'StatusCode
Status'STATUS_CODE_UNSET
  maybeToEnum Int
1 = Status'StatusCode -> Maybe Status'StatusCode
forall a. a -> Maybe a
Prelude.Just Status'StatusCode
Status'STATUS_CODE_OK
  maybeToEnum Int
2 = Status'StatusCode -> Maybe Status'StatusCode
forall a. a -> Maybe a
Prelude.Just Status'StatusCode
Status'STATUS_CODE_ERROR
  maybeToEnum Int
k
    = Status'StatusCode -> Maybe Status'StatusCode
forall a. a -> Maybe a
Prelude.Just
        (Status'StatusCode'UnrecognizedValue -> Status'StatusCode
Status'StatusCode'Unrecognized
           (Int32 -> Status'StatusCode'UnrecognizedValue
Status'StatusCode'UnrecognizedValue (Int -> Int32
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Int
k)))
  showEnum :: Status'StatusCode -> String
showEnum Status'StatusCode
Status'STATUS_CODE_UNSET = String
"STATUS_CODE_UNSET"
  showEnum Status'StatusCode
Status'STATUS_CODE_OK = String
"STATUS_CODE_OK"
  showEnum Status'StatusCode
Status'STATUS_CODE_ERROR = String
"STATUS_CODE_ERROR"
  showEnum
    (Status'StatusCode'Unrecognized (Status'StatusCode'UnrecognizedValue Int32
k))
    = Int32 -> String
forall a. Show a => a -> String
Prelude.show Int32
k
  readEnum :: String -> Maybe Status'StatusCode
readEnum String
k
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"STATUS_CODE_UNSET"
    = Status'StatusCode -> Maybe Status'StatusCode
forall a. a -> Maybe a
Prelude.Just Status'StatusCode
Status'STATUS_CODE_UNSET
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"STATUS_CODE_OK"
    = Status'StatusCode -> Maybe Status'StatusCode
forall a. a -> Maybe a
Prelude.Just Status'StatusCode
Status'STATUS_CODE_OK
    | String -> String -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) String
k String
"STATUS_CODE_ERROR"
    = Status'StatusCode -> Maybe Status'StatusCode
forall a. a -> Maybe a
Prelude.Just Status'StatusCode
Status'STATUS_CODE_ERROR
    | Bool
Prelude.otherwise
    = Maybe Int
-> (Int -> Maybe Status'StatusCode) -> Maybe Status'StatusCode
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
(Prelude.>>=) (String -> Maybe Int
forall a. Read a => String -> Maybe a
Text.Read.readMaybe String
k) Int -> Maybe Status'StatusCode
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum
instance Prelude.Bounded Status'StatusCode where
  minBound :: Status'StatusCode
minBound = Status'StatusCode
Status'STATUS_CODE_UNSET
  maxBound :: Status'StatusCode
maxBound = Status'StatusCode
Status'STATUS_CODE_ERROR
instance Prelude.Enum Status'StatusCode where
  toEnum :: Int -> Status'StatusCode
toEnum Int
k__
    = Status'StatusCode
-> (Status'StatusCode -> Status'StatusCode)
-> Maybe Status'StatusCode
-> Status'StatusCode
forall b a. b -> (a -> b) -> Maybe a -> b
Prelude.maybe
        (String -> Status'StatusCode
forall a. HasCallStack => String -> a
Prelude.error
           (String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
              String
"toEnum: unknown value for enum StatusCode: " (Int -> String
forall a. Show a => a -> String
Prelude.show Int
k__)))
        Status'StatusCode -> Status'StatusCode
forall a. a -> a
Prelude.id (Int -> Maybe Status'StatusCode
forall a. MessageEnum a => Int -> Maybe a
Data.ProtoLens.maybeToEnum Int
k__)
  fromEnum :: Status'StatusCode -> Int
fromEnum Status'StatusCode
Status'STATUS_CODE_UNSET = Int
0
  fromEnum Status'StatusCode
Status'STATUS_CODE_OK = Int
1
  fromEnum Status'StatusCode
Status'STATUS_CODE_ERROR = Int
2
  fromEnum
    (Status'StatusCode'Unrecognized (Status'StatusCode'UnrecognizedValue Int32
k))
    = Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Int32
k
  succ :: Status'StatusCode -> Status'StatusCode
succ Status'StatusCode
Status'STATUS_CODE_ERROR
    = String -> Status'StatusCode
forall a. HasCallStack => String -> a
Prelude.error
        String
"Status'StatusCode.succ: bad argument Status'STATUS_CODE_ERROR. This value would be out of bounds."
  succ Status'StatusCode
Status'STATUS_CODE_UNSET = Status'StatusCode
Status'STATUS_CODE_OK
  succ Status'StatusCode
Status'STATUS_CODE_OK = Status'StatusCode
Status'STATUS_CODE_ERROR
  succ (Status'StatusCode'Unrecognized Status'StatusCode'UnrecognizedValue
_)
    = String -> Status'StatusCode
forall a. HasCallStack => String -> a
Prelude.error
        String
"Status'StatusCode.succ: bad argument: unrecognized value"
  pred :: Status'StatusCode -> Status'StatusCode
pred Status'StatusCode
Status'STATUS_CODE_UNSET
    = String -> Status'StatusCode
forall a. HasCallStack => String -> a
Prelude.error
        String
"Status'StatusCode.pred: bad argument Status'STATUS_CODE_UNSET. This value would be out of bounds."
  pred Status'StatusCode
Status'STATUS_CODE_OK = Status'StatusCode
Status'STATUS_CODE_UNSET
  pred Status'StatusCode
Status'STATUS_CODE_ERROR = Status'StatusCode
Status'STATUS_CODE_OK
  pred (Status'StatusCode'Unrecognized Status'StatusCode'UnrecognizedValue
_)
    = String -> Status'StatusCode
forall a. HasCallStack => String -> a
Prelude.error
        String
"Status'StatusCode.pred: bad argument: unrecognized value"
  enumFrom :: Status'StatusCode -> [Status'StatusCode]
enumFrom = Status'StatusCode -> [Status'StatusCode]
forall a. (Enum a, Bounded a) => a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFrom
  enumFromTo :: Status'StatusCode -> Status'StatusCode -> [Status'StatusCode]
enumFromTo = Status'StatusCode -> Status'StatusCode -> [Status'StatusCode]
forall a. Enum a => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromTo
  enumFromThen :: Status'StatusCode -> Status'StatusCode -> [Status'StatusCode]
enumFromThen = Status'StatusCode -> Status'StatusCode -> [Status'StatusCode]
forall a. (Enum a, Bounded a) => a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThen
  enumFromThenTo :: Status'StatusCode
-> Status'StatusCode -> Status'StatusCode -> [Status'StatusCode]
enumFromThenTo = Status'StatusCode
-> Status'StatusCode -> Status'StatusCode -> [Status'StatusCode]
forall a. Enum a => a -> a -> a -> [a]
Data.ProtoLens.Message.Enum.messageEnumFromThenTo
instance Data.ProtoLens.FieldDefault Status'StatusCode where
  fieldDefault :: Status'StatusCode
fieldDefault = Status'StatusCode
Status'STATUS_CODE_UNSET
instance Control.DeepSeq.NFData Status'StatusCode where
  rnf :: Status'StatusCode -> ()
rnf Status'StatusCode
x__ = Status'StatusCode -> () -> ()
Prelude.seq Status'StatusCode
x__ ()
{- | Fields :
     
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.resourceSpans' @:: Lens' TracesData [ResourceSpans]@
         * 'Proto.Opentelemetry.Proto.Trace.V1.Trace_Fields.vec'resourceSpans' @:: Lens' TracesData (Data.Vector.Vector ResourceSpans)@ -}
data TracesData
  = TracesData'_constructor {TracesData -> Vector ResourceSpans
_TracesData'resourceSpans :: !(Data.Vector.Vector ResourceSpans),
                             TracesData -> FieldSet
_TracesData'_unknownFields :: !Data.ProtoLens.FieldSet}
  deriving stock (TracesData -> TracesData -> Bool
(TracesData -> TracesData -> Bool)
-> (TracesData -> TracesData -> Bool) -> Eq TracesData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TracesData -> TracesData -> Bool
$c/= :: TracesData -> TracesData -> Bool
== :: TracesData -> TracesData -> Bool
$c== :: TracesData -> TracesData -> Bool
Prelude.Eq, Eq TracesData
Eq TracesData
-> (TracesData -> TracesData -> Ordering)
-> (TracesData -> TracesData -> Bool)
-> (TracesData -> TracesData -> Bool)
-> (TracesData -> TracesData -> Bool)
-> (TracesData -> TracesData -> Bool)
-> (TracesData -> TracesData -> TracesData)
-> (TracesData -> TracesData -> TracesData)
-> Ord TracesData
TracesData -> TracesData -> Bool
TracesData -> TracesData -> Ordering
TracesData -> TracesData -> TracesData
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 :: TracesData -> TracesData -> TracesData
$cmin :: TracesData -> TracesData -> TracesData
max :: TracesData -> TracesData -> TracesData
$cmax :: TracesData -> TracesData -> TracesData
>= :: TracesData -> TracesData -> Bool
$c>= :: TracesData -> TracesData -> Bool
> :: TracesData -> TracesData -> Bool
$c> :: TracesData -> TracesData -> Bool
<= :: TracesData -> TracesData -> Bool
$c<= :: TracesData -> TracesData -> Bool
< :: TracesData -> TracesData -> Bool
$c< :: TracesData -> TracesData -> Bool
compare :: TracesData -> TracesData -> Ordering
$ccompare :: TracesData -> TracesData -> Ordering
$cp1Ord :: Eq TracesData
Prelude.Ord)
instance Prelude.Show TracesData where
  showsPrec :: Int -> TracesData -> ShowS
showsPrec Int
_ TracesData
__x String
__s
    = Char -> ShowS
Prelude.showChar
        Char
'{'
        (String -> ShowS
Prelude.showString
           (TracesData -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort TracesData
__x) (Char -> ShowS
Prelude.showChar Char
'}' String
__s))
instance Data.ProtoLens.Field.HasField TracesData "resourceSpans" [ResourceSpans] where
  fieldOf :: Proxy# "resourceSpans"
-> ([ResourceSpans] -> f [ResourceSpans])
-> TracesData
-> f TracesData
fieldOf Proxy# "resourceSpans"
_
    = ((Vector ResourceSpans -> f (Vector ResourceSpans))
 -> TracesData -> f TracesData)
-> (([ResourceSpans] -> f [ResourceSpans])
    -> Vector ResourceSpans -> f (Vector ResourceSpans))
-> ([ResourceSpans] -> f [ResourceSpans])
-> TracesData
-> f TracesData
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((TracesData -> Vector ResourceSpans)
-> (TracesData -> Vector ResourceSpans -> TracesData)
-> Lens
     TracesData TracesData (Vector ResourceSpans) (Vector ResourceSpans)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           TracesData -> Vector ResourceSpans
_TracesData'resourceSpans
           (\ TracesData
x__ Vector ResourceSpans
y__ -> TracesData
x__ {_TracesData'resourceSpans :: Vector ResourceSpans
_TracesData'resourceSpans = Vector ResourceSpans
y__}))
        ((Vector ResourceSpans -> [ResourceSpans])
-> (Vector ResourceSpans
    -> [ResourceSpans] -> Vector ResourceSpans)
-> Lens
     (Vector ResourceSpans)
     (Vector ResourceSpans)
     [ResourceSpans]
     [ResourceSpans]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           Vector ResourceSpans -> [ResourceSpans]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
           (\ Vector ResourceSpans
_ [ResourceSpans]
y__ -> [ResourceSpans] -> Vector ResourceSpans
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [ResourceSpans]
y__))
instance Data.ProtoLens.Field.HasField TracesData "vec'resourceSpans" (Data.Vector.Vector ResourceSpans) where
  fieldOf :: Proxy# "vec'resourceSpans"
-> (Vector ResourceSpans -> f (Vector ResourceSpans))
-> TracesData
-> f TracesData
fieldOf Proxy# "vec'resourceSpans"
_
    = ((Vector ResourceSpans -> f (Vector ResourceSpans))
 -> TracesData -> f TracesData)
-> ((Vector ResourceSpans -> f (Vector ResourceSpans))
    -> Vector ResourceSpans -> f (Vector ResourceSpans))
-> (Vector ResourceSpans -> f (Vector ResourceSpans))
-> TracesData
-> f TracesData
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
        ((TracesData -> Vector ResourceSpans)
-> (TracesData -> Vector ResourceSpans -> TracesData)
-> Lens
     TracesData TracesData (Vector ResourceSpans) (Vector ResourceSpans)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
           TracesData -> Vector ResourceSpans
_TracesData'resourceSpans
           (\ TracesData
x__ Vector ResourceSpans
y__ -> TracesData
x__ {_TracesData'resourceSpans :: Vector ResourceSpans
_TracesData'resourceSpans = Vector ResourceSpans
y__}))
        (Vector ResourceSpans -> f (Vector ResourceSpans))
-> Vector ResourceSpans -> f (Vector ResourceSpans)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message TracesData where
  messageName :: Proxy TracesData -> Text
messageName Proxy TracesData
_
    = String -> Text
Data.Text.pack String
"opentelemetry.proto.trace.v1.TracesData"
  packedMessageDescriptor :: Proxy TracesData -> ByteString
packedMessageDescriptor Proxy TracesData
_
    = ByteString
"\n\
      \\n\
      \TracesData\DC2R\n\
      \\SOresource_spans\CAN\SOH \ETX(\v2+.opentelemetry.proto.trace.v1.ResourceSpansR\rresourceSpans"
  packedFileDescriptor :: Proxy TracesData -> ByteString
packedFileDescriptor Proxy TracesData
_ = ByteString
packedFileDescriptor
  fieldsByTag :: Map Tag (FieldDescriptor TracesData)
fieldsByTag
    = let
        resourceSpans__field_descriptor :: FieldDescriptor TracesData
resourceSpans__field_descriptor
          = String
-> FieldTypeDescriptor ResourceSpans
-> FieldAccessor TracesData ResourceSpans
-> FieldDescriptor TracesData
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
              String
"resource_spans"
              (MessageOrGroup -> FieldTypeDescriptor ResourceSpans
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
                 Data.ProtoLens.FieldTypeDescriptor ResourceSpans)
              (Packing
-> Lens' TracesData [ResourceSpans]
-> FieldAccessor TracesData ResourceSpans
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
                 Packing
Data.ProtoLens.Unpacked
                 (forall s a (f :: * -> *).
(HasField s "resourceSpans" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"resourceSpans")) ::
              Data.ProtoLens.FieldDescriptor TracesData
      in
        [(Tag, FieldDescriptor TracesData)]
-> Map Tag (FieldDescriptor TracesData)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
          [(Int -> Tag
Data.ProtoLens.Tag Int
1, FieldDescriptor TracesData
resourceSpans__field_descriptor)]
  unknownFields :: LensLike' f TracesData FieldSet
unknownFields
    = (TracesData -> FieldSet)
-> (TracesData -> FieldSet -> TracesData)
-> Lens' TracesData FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
        TracesData -> FieldSet
_TracesData'_unknownFields
        (\ TracesData
x__ FieldSet
y__ -> TracesData
x__ {_TracesData'_unknownFields :: FieldSet
_TracesData'_unknownFields = FieldSet
y__})
  defMessage :: TracesData
defMessage
    = TracesData'_constructor :: Vector ResourceSpans -> FieldSet -> TracesData
TracesData'_constructor
        {_TracesData'resourceSpans :: Vector ResourceSpans
_TracesData'resourceSpans = Vector ResourceSpans
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
         _TracesData'_unknownFields :: FieldSet
_TracesData'_unknownFields = []}
  parseMessage :: Parser TracesData
parseMessage
    = let
        loop ::
          TracesData
          -> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld ResourceSpans
             -> Data.ProtoLens.Encoding.Bytes.Parser TracesData
        loop :: TracesData
-> Growing Vector RealWorld ResourceSpans -> Parser TracesData
loop TracesData
x Growing Vector RealWorld ResourceSpans
mutable'resourceSpans
          = do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
               if Bool
end then
                   do Vector ResourceSpans
frozen'resourceSpans <- IO (Vector ResourceSpans) -> Parser (Vector ResourceSpans)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                                (Growing Vector (PrimState IO) ResourceSpans
-> IO (Vector ResourceSpans)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> m (v a)
Data.ProtoLens.Encoding.Growing.unsafeFreeze
                                                   Growing Vector RealWorld ResourceSpans
Growing Vector (PrimState IO) ResourceSpans
mutable'resourceSpans)
                      (let missing :: [a]
missing = []
                       in
                         if [Any] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [Any]
forall a. [a]
missing then
                             () -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
                         else
                             String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
                               (String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
                                  String
"Missing required fields: "
                                  ([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
forall a. [a]
missing :: [Prelude.String]))))
                      TracesData -> Parser TracesData
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
                        (Setter TracesData TracesData FieldSet FieldSet
-> (FieldSet -> FieldSet) -> TracesData -> TracesData
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
                           forall msg. Message msg => Lens' msg FieldSet
Setter TracesData TracesData FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
                           (Setter
  TracesData TracesData (Vector ResourceSpans) (Vector ResourceSpans)
-> Vector ResourceSpans -> TracesData -> TracesData
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
                              (forall s a (f :: * -> *).
(HasField s "vec'resourceSpans" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'resourceSpans")
                              Vector ResourceSpans
frozen'resourceSpans TracesData
x))
               else
                   do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                      case Word64
tag of
                        Word64
10
                          -> do !ResourceSpans
y <- Parser ResourceSpans -> String -> Parser ResourceSpans
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
                                        (do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
                                            Int -> Parser ResourceSpans -> Parser ResourceSpans
forall a. Int -> Parser a -> Parser a
Data.ProtoLens.Encoding.Bytes.isolate
                                              (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral Word64
len)
                                              Parser ResourceSpans
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
                                        String
"resource_spans"
                                Growing Vector RealWorld ResourceSpans
v <- IO (Growing Vector RealWorld ResourceSpans)
-> Parser (Growing Vector RealWorld ResourceSpans)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                       (Growing Vector (PrimState IO) ResourceSpans
-> ResourceSpans
-> IO (Growing Vector (PrimState IO) ResourceSpans)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Growing v (PrimState m) a -> a -> m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.append
                                          Growing Vector RealWorld ResourceSpans
Growing Vector (PrimState IO) ResourceSpans
mutable'resourceSpans ResourceSpans
y)
                                TracesData
-> Growing Vector RealWorld ResourceSpans -> Parser TracesData
loop TracesData
x Growing Vector RealWorld ResourceSpans
v
                        Word64
wire
                          -> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
                                        Word64
wire
                                TracesData
-> Growing Vector RealWorld ResourceSpans -> Parser TracesData
loop
                                  (Setter TracesData TracesData FieldSet FieldSet
-> (FieldSet -> FieldSet) -> TracesData -> TracesData
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
                                     forall msg. Message msg => Lens' msg FieldSet
Setter TracesData TracesData FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) TracesData
x)
                                  Growing Vector RealWorld ResourceSpans
mutable'resourceSpans
      in
        Parser TracesData -> String -> Parser TracesData
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
          (do Growing Vector RealWorld ResourceSpans
mutable'resourceSpans <- IO (Growing Vector RealWorld ResourceSpans)
-> Parser (Growing Vector RealWorld ResourceSpans)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
                                         IO (Growing Vector RealWorld ResourceSpans)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
              TracesData
-> Growing Vector RealWorld ResourceSpans -> Parser TracesData
loop TracesData
forall msg. Message msg => msg
Data.ProtoLens.defMessage Growing Vector RealWorld ResourceSpans
mutable'resourceSpans)
          String
"TracesData"
  buildMessage :: TracesData -> Builder
buildMessage
    = \ TracesData
_x
        -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
             ((ResourceSpans -> Builder) -> Vector ResourceSpans -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
                (\ ResourceSpans
_v
                   -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                        (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
10)
                        ((ByteString -> Builder)
-> (ResourceSpans -> ByteString) -> ResourceSpans -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
                           (\ ByteString
bs
                              -> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
                                   (Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt
                                      (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral (ByteString -> Int
Data.ByteString.length ByteString
bs)))
                                   (ByteString -> Builder
Data.ProtoLens.Encoding.Bytes.putBytes ByteString
bs))
                           ResourceSpans -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage ResourceSpans
_v))
                (FoldLike
  (Vector ResourceSpans)
  TracesData
  TracesData
  (Vector ResourceSpans)
  (Vector ResourceSpans)
-> TracesData -> Vector ResourceSpans
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
                   (forall s a (f :: * -> *).
(HasField s "vec'resourceSpans" a, Functor f) =>
(a -> f a) -> s -> f s
forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'resourceSpans") TracesData
_x))
             (FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
                (FoldLike FieldSet TracesData TracesData FieldSet FieldSet
-> TracesData -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet TracesData TracesData FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Data.ProtoLens.unknownFields TracesData
_x))
instance Control.DeepSeq.NFData TracesData where
  rnf :: TracesData -> ()
rnf
    = \ TracesData
x__
        -> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
             (TracesData -> FieldSet
_TracesData'_unknownFields TracesData
x__)
             (Vector ResourceSpans -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (TracesData -> Vector ResourceSpans
_TracesData'resourceSpans TracesData
x__) ())
packedFileDescriptor :: Data.ByteString.ByteString
packedFileDescriptor :: ByteString
packedFileDescriptor
  = ByteString
"\n\
    \(opentelemetry/proto/trace/v1/trace.proto\DC2\FSopentelemetry.proto.trace.v1\SUB*opentelemetry/proto/common/v1/common.proto\SUB.opentelemetry/proto/resource/v1/resource.proto\"`\n\
    \\n\
    \TracesData\DC2R\n\
    \\SOresource_spans\CAN\SOH \ETX(\v2+.opentelemetry.proto.trace.v1.ResourceSpansR\rresourceSpans\"\244\SOH\n\
    \\rResourceSpans\DC2E\n\
    \\bresource\CAN\SOH \SOH(\v2).opentelemetry.proto.resource.v1.ResourceR\bresource\DC2}\n\
    \\GSinstrumentation_library_spans\CAN\STX \ETX(\v29.opentelemetry.proto.trace.v1.InstrumentationLibrarySpansR\ESCinstrumentationLibrarySpans\DC2\GS\n\
    \\n\
    \schema_url\CAN\ETX \SOH(\tR\tschemaUrl\"\230\SOH\n\
    \\ESCInstrumentationLibrarySpans\DC2n\n\
    \\ETBinstrumentation_library\CAN\SOH \SOH(\v25.opentelemetry.proto.common.v1.InstrumentationLibraryR\SYNinstrumentationLibrary\DC28\n\
    \\ENQspans\CAN\STX \ETX(\v2\".opentelemetry.proto.trace.v1.SpanR\ENQspans\DC2\GS\n\
    \\n\
    \schema_url\CAN\ETX \SOH(\tR\tschemaUrl\"\156\n\
    \\n\
    \\EOTSpan\DC2\EM\n\
    \\btrace_id\CAN\SOH \SOH(\fR\atraceId\DC2\ETB\n\
    \\aspan_id\CAN\STX \SOH(\fR\ACKspanId\DC2\US\n\
    \\vtrace_state\CAN\ETX \SOH(\tR\n\
    \traceState\DC2$\n\
    \\SOparent_span_id\CAN\EOT \SOH(\fR\fparentSpanId\DC2\DC2\n\
    \\EOTname\CAN\ENQ \SOH(\tR\EOTname\DC2?\n\
    \\EOTkind\CAN\ACK \SOH(\SO2+.opentelemetry.proto.trace.v1.Span.SpanKindR\EOTkind\DC2/\n\
    \\DC4start_time_unix_nano\CAN\a \SOH(\ACKR\DC1startTimeUnixNano\DC2+\n\
    \\DC2end_time_unix_nano\CAN\b \SOH(\ACKR\SIendTimeUnixNano\DC2G\n\
    \\n\
    \attributes\CAN\t \ETX(\v2'.opentelemetry.proto.common.v1.KeyValueR\n\
    \attributes\DC28\n\
    \\CANdropped_attributes_count\CAN\n\
    \ \SOH(\rR\SYNdroppedAttributesCount\DC2@\n\
    \\ACKevents\CAN\v \ETX(\v2(.opentelemetry.proto.trace.v1.Span.EventR\ACKevents\DC20\n\
    \\DC4dropped_events_count\CAN\f \SOH(\rR\DC2droppedEventsCount\DC2=\n\
    \\ENQlinks\CAN\r \ETX(\v2'.opentelemetry.proto.trace.v1.Span.LinkR\ENQlinks\DC2.\n\
    \\DC3dropped_links_count\CAN\SO \SOH(\rR\DC1droppedLinksCount\DC2<\n\
    \\ACKstatus\CAN\SI \SOH(\v2$.opentelemetry.proto.trace.v1.StatusR\ACKstatus\SUB\196\SOH\n\
    \\ENQEvent\DC2$\n\
    \\SOtime_unix_nano\CAN\SOH \SOH(\ACKR\ftimeUnixNano\DC2\DC2\n\
    \\EOTname\CAN\STX \SOH(\tR\EOTname\DC2G\n\
    \\n\
    \attributes\CAN\ETX \ETX(\v2'.opentelemetry.proto.common.v1.KeyValueR\n\
    \attributes\DC28\n\
    \\CANdropped_attributes_count\CAN\EOT \SOH(\rR\SYNdroppedAttributesCount\SUB\222\SOH\n\
    \\EOTLink\DC2\EM\n\
    \\btrace_id\CAN\SOH \SOH(\fR\atraceId\DC2\ETB\n\
    \\aspan_id\CAN\STX \SOH(\fR\ACKspanId\DC2\US\n\
    \\vtrace_state\CAN\ETX \SOH(\tR\n\
    \traceState\DC2G\n\
    \\n\
    \attributes\CAN\EOT \ETX(\v2'.opentelemetry.proto.common.v1.KeyValueR\n\
    \attributes\DC28\n\
    \\CANdropped_attributes_count\CAN\ENQ \SOH(\rR\SYNdroppedAttributesCount\"\153\SOH\n\
    \\bSpanKind\DC2\EM\n\
    \\NAKSPAN_KIND_UNSPECIFIED\DLE\NUL\DC2\SYN\n\
    \\DC2SPAN_KIND_INTERNAL\DLE\SOH\DC2\DC4\n\
    \\DLESPAN_KIND_SERVER\DLE\STX\DC2\DC4\n\
    \\DLESPAN_KIND_CLIENT\DLE\ETX\DC2\SYN\n\
    \\DC2SPAN_KIND_PRODUCER\DLE\EOT\DC2\SYN\n\
    \\DC2SPAN_KIND_CONSUMER\DLE\ENQ\"\252\a\n\
    \\ACKStatus\DC2f\n\
    \\SIdeprecated_code\CAN\SOH \SOH(\SO29.opentelemetry.proto.trace.v1.Status.DeprecatedStatusCodeR\SOdeprecatedCodeB\STX\CAN\SOH\DC2\CAN\n\
    \\amessage\CAN\STX \SOH(\tR\amessage\DC2C\n\
    \\EOTcode\CAN\ETX \SOH(\SO2/.opentelemetry.proto.trace.v1.Status.StatusCodeR\EOTcode\"\218\ENQ\n\
    \\DC4DeprecatedStatusCode\DC2\GS\n\
    \\EMDEPRECATED_STATUS_CODE_OK\DLE\NUL\DC2$\n\
    \ DEPRECATED_STATUS_CODE_CANCELLED\DLE\SOH\DC2(\n\
    \$DEPRECATED_STATUS_CODE_UNKNOWN_ERROR\DLE\STX\DC2+\n\
    \'DEPRECATED_STATUS_CODE_INVALID_ARGUMENT\DLE\ETX\DC2,\n\
    \(DEPRECATED_STATUS_CODE_DEADLINE_EXCEEDED\DLE\EOT\DC2$\n\
    \ DEPRECATED_STATUS_CODE_NOT_FOUND\DLE\ENQ\DC2)\n\
    \%DEPRECATED_STATUS_CODE_ALREADY_EXISTS\DLE\ACK\DC2,\n\
    \(DEPRECATED_STATUS_CODE_PERMISSION_DENIED\DLE\a\DC2-\n\
    \)DEPRECATED_STATUS_CODE_RESOURCE_EXHAUSTED\DLE\b\DC2.\n\
    \*DEPRECATED_STATUS_CODE_FAILED_PRECONDITION\DLE\t\DC2\"\n\
    \\RSDEPRECATED_STATUS_CODE_ABORTED\DLE\n\
    \\DC2'\n\
    \#DEPRECATED_STATUS_CODE_OUT_OF_RANGE\DLE\v\DC2(\n\
    \$DEPRECATED_STATUS_CODE_UNIMPLEMENTED\DLE\f\DC2)\n\
    \%DEPRECATED_STATUS_CODE_INTERNAL_ERROR\DLE\r\DC2&\n\
    \\"DEPRECATED_STATUS_CODE_UNAVAILABLE\DLE\SO\DC2$\n\
    \ DEPRECATED_STATUS_CODE_DATA_LOSS\DLE\SI\DC2*\n\
    \&DEPRECATED_STATUS_CODE_UNAUTHENTICATED\DLE\DLE\"N\n\
    \\n\
    \StatusCode\DC2\NAK\n\
    \\DC1STATUS_CODE_UNSET\DLE\NUL\DC2\DC2\n\
    \\SOSTATUS_CODE_OK\DLE\SOH\DC2\NAK\n\
    \\DC1STATUS_CODE_ERROR\DLE\STXBn\n\
    \\USio.opentelemetry.proto.trace.v1B\n\
    \TraceProtoP\SOHZ=github.com/open-telemetry/opentelemetry-proto/gen/go/trace/v1J\146x\n\
    \\a\DC2\ENQ\SO\NUL\214\STX\SOH\n\
    \\200\EOT\n\
    \\SOH\f\DC2\ETX\SO\NUL\DC22\189\EOT Copyright 2019, OpenTelemetry Authors\n\
    \\n\
    \ Licensed under the Apache License, Version 2.0 (the \"License\");\n\
    \ you may not use this file except in compliance with the License.\n\
    \ You may obtain a copy of the License at\n\
    \\n\
    \     http://www.apache.org/licenses/LICENSE-2.0\n\
    \\n\
    \ Unless required by applicable law or agreed to in writing, software\n\
    \ distributed under the License is distributed on an \"AS IS\" BASIS,\n\
    \ WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.\n\
    \ See the License for the specific language governing permissions and\n\
    \ limitations under the License.\n\
    \\n\
    \\b\n\
    \\SOH\STX\DC2\ETX\DLE\NUL%\n\
    \\t\n\
    \\STX\ETX\NUL\DC2\ETX\DC2\NUL4\n\
    \\t\n\
    \\STX\ETX\SOH\DC2\ETX\DC3\NUL8\n\
    \\b\n\
    \\SOH\b\DC2\ETX\NAK\NUL\"\n\
    \\t\n\
    \\STX\b\n\
    \\DC2\ETX\NAK\NUL\"\n\
    \\b\n\
    \\SOH\b\DC2\ETX\SYN\NUL8\n\
    \\t\n\
    \\STX\b\SOH\DC2\ETX\SYN\NUL8\n\
    \\b\n\
    \\SOH\b\DC2\ETX\ETB\NUL+\n\
    \\t\n\
    \\STX\b\b\DC2\ETX\ETB\NUL+\n\
    \\b\n\
    \\SOH\b\DC2\ETX\CAN\NULT\n\
    \\t\n\
    \\STX\b\v\DC2\ETX\CAN\NULT\n\
    \\206\ETX\n\
    \\STX\EOT\NUL\DC2\EOT$\NUL+\SOH\SUB\193\ETX TracesData represents the traces data that can be stored in a persistent storage,\n\
    \ OR can be embedded by other protocols that transfer OTLP traces data but do\n\
    \ not implement the OTLP protocol.\n\
    \\n\
    \ The main difference between this message and collector protocol is that\n\
    \ in this message there will not be any \"control\" or \"metadata\" specific to\n\
    \ OTLP protocol.\n\
    \\n\
    \ When new fields are added into this message, the OTLP request MUST be updated\n\
    \ as well.\n\
    \\n\
    \\n\
    \\n\
    \\ETX\EOT\NUL\SOH\DC2\ETX$\b\DC2\n\
    \\174\STX\n\
    \\EOT\EOT\NUL\STX\NUL\DC2\ETX*\STX,\SUB\160\STX An array of ResourceSpans.\n\
    \ For data coming from a single resource this array will typically contain\n\
    \ one element. Intermediary nodes that receive data from multiple origins\n\
    \ typically batch the data before forwarding further and in that case this\n\
    \ array will contain multiple elements.\n\
    \\n\
    \\f\n\
    \\ENQ\EOT\NUL\STX\NUL\EOT\DC2\ETX*\STX\n\
    \\n\
    \\f\n\
    \\ENQ\EOT\NUL\STX\NUL\ACK\DC2\ETX*\v\CAN\n\
    \\f\n\
    \\ENQ\EOT\NUL\STX\NUL\SOH\DC2\ETX*\EM'\n\
    \\f\n\
    \\ENQ\EOT\NUL\STX\NUL\ETX\DC2\ETX**+\n\
    \J\n\
    \\STX\EOT\SOH\DC2\EOT.\NUL:\SOH\SUB> A collection of InstrumentationLibrarySpans from a Resource.\n\
    \\n\
    \\n\
    \\n\
    \\ETX\EOT\SOH\SOH\DC2\ETX.\b\NAK\n\
    \t\n\
    \\EOT\EOT\SOH\STX\NUL\DC2\ETX1\STX8\SUBg The resource for the spans in this message.\n\
    \ If this field is not set then no resource info is known.\n\
    \\n\
    \\f\n\
    \\ENQ\EOT\SOH\STX\NUL\ACK\DC2\ETX1\STX*\n\
    \\f\n\
    \\ENQ\EOT\SOH\STX\NUL\SOH\DC2\ETX1+3\n\
    \\f\n\
    \\ENQ\EOT\SOH\STX\NUL\ETX\DC2\ETX167\n\
    \T\n\
    \\EOT\EOT\SOH\STX\SOH\DC2\ETX4\STXI\SUBG A list of InstrumentationLibrarySpans that originate from a resource.\n\
    \\n\
    \\f\n\
    \\ENQ\EOT\SOH\STX\SOH\EOT\DC2\ETX4\STX\n\
    \\n\
    \\f\n\
    \\ENQ\EOT\SOH\STX\SOH\ACK\DC2\ETX4\v&\n\
    \\f\n\
    \\ENQ\EOT\SOH\STX\SOH\SOH\DC2\ETX4'D\n\
    \\f\n\
    \\ENQ\EOT\SOH\STX\SOH\ETX\DC2\ETX4GH\n\
    \\192\SOH\n\
    \\EOT\EOT\SOH\STX\STX\DC2\ETX9\STX\CAN\SUB\178\SOH This schema_url applies to the data in the \"resource\" field. It does not apply\n\
    \ to the data in the \"instrumentation_library_spans\" field which have their own\n\
    \ schema_url field.\n\
    \\n\
    \\f\n\
    \\ENQ\EOT\SOH\STX\STX\ENQ\DC2\ETX9\STX\b\n\
    \\f\n\
    \\ENQ\EOT\SOH\STX\STX\SOH\DC2\ETX9\t\DC3\n\
    \\f\n\
    \\ENQ\EOT\SOH\STX\STX\ETX\DC2\ETX9\SYN\ETB\n\
    \J\n\
    \\STX\EOT\STX\DC2\EOT=\NULH\SOH\SUB> A collection of Spans produced by an InstrumentationLibrary.\n\
    \\n\
    \\n\
    \\n\
    \\ETX\EOT\STX\SOH\DC2\ETX=\b#\n\
    \\211\SOH\n\
    \\EOT\EOT\STX\STX\NUL\DC2\ETXA\STXS\SUB\197\SOH The instrumentation library information for the spans in this message.\n\
    \ Semantically when InstrumentationLibrary isn't set, it is equivalent with\n\
    \ an empty instrumentation library name (unknown).\n\
    \\n\
    \\f\n\
    \\ENQ\EOT\STX\STX\NUL\ACK\DC2\ETXA\STX6\n\
    \\f\n\
    \\ENQ\EOT\STX\STX\NUL\SOH\DC2\ETXA7N\n\
    \\f\n\
    \\ENQ\EOT\STX\STX\NUL\ETX\DC2\ETXAQR\n\
    \N\n\
    \\EOT\EOT\STX\STX\SOH\DC2\ETXD\STX\SUB\SUBA A list of Spans that originate from an instrumentation library.\n\
    \\n\
    \\f\n\
    \\ENQ\EOT\STX\STX\SOH\EOT\DC2\ETXD\STX\n\
    \\n\
    \\f\n\
    \\ENQ\EOT\STX\STX\SOH\ACK\DC2\ETXD\v\SI\n\
    \\f\n\
    \\ENQ\EOT\STX\STX\SOH\SOH\DC2\ETXD\DLE\NAK\n\
    \\f\n\
    \\ENQ\EOT\STX\STX\SOH\ETX\DC2\ETXD\CAN\EM\n\
    \Y\n\
    \\EOT\EOT\STX\STX\STX\DC2\ETXG\STX\CAN\SUBL This schema_url applies to all spans and span events in the \"spans\" field.\n\
    \\n\
    \\f\n\
    \\ENQ\EOT\STX\STX\STX\ENQ\DC2\ETXG\STX\b\n\
    \\f\n\
    \\ENQ\EOT\STX\STX\STX\SOH\DC2\ETXG\t\DC3\n\
    \\f\n\
    \\ENQ\EOT\STX\STX\STX\ETX\DC2\ETXG\SYN\ETB\n\
    \\136\EOT\n\
    \\STX\EOT\ETX\DC2\ENQS\NUL\253\SOH\SOH\SUB\250\ETX Span represents a single operation within a trace. Spans can be\n\
    \ nested to form a trace tree. Spans may also be linked to other spans\n\
    \ from the same or different trace and form graphs. Often, a trace\n\
    \ contains a root span that describes the end-to-end latency, and one\n\
    \ or more subspans for its sub-operations. A trace can also contain\n\
    \ multiple root spans, or none at all. Spans do not need to be\n\
    \ contiguous - there may be gaps or overlaps between spans in a trace.\n\
    \\n\
    \ The next available field id is 17.\n\
    \\n\
    \\n\
    \\n\
    \\ETX\EOT\ETX\SOH\DC2\ETXS\b\f\n\
    \\205\STX\n\
    \\EOT\EOT\ETX\STX\NUL\DC2\ETX\\\STX\NAK\SUB\191\STX A unique identifier for a trace. All spans from the same trace share\n\
    \ the same `trace_id`. The ID is a 16-byte array. An ID with all zeroes\n\
    \ is considered invalid.\n\
    \\n\
    \ This field is semantically required. Receiver should generate new\n\
    \ random trace_id if empty or invalid trace_id was received.\n\
    \\n\
    \ This field is required.\n\
    \\n\
    \\f\n\
    \\ENQ\EOT\ETX\STX\NUL\ENQ\DC2\ETX\\\STX\a\n\
    \\f\n\
    \\ENQ\EOT\ETX\STX\NUL\SOH\DC2\ETX\\\b\DLE\n\
    \\f\n\
    \\ENQ\EOT\ETX\STX\NUL\ETX\DC2\ETX\\\DC3\DC4\n\
    \\195\STX\n\
    \\EOT\EOT\ETX\STX\SOH\DC2\ETXf\STX\DC4\SUB\181\STX A unique identifier for a span within a trace, assigned when the span\n\
    \ is created. The ID is an 8-byte array. An ID with all zeroes is considered\n\
    \ invalid.\n\
    \\n\
    \ This field is semantically required. Receiver should generate new\n\
    \ random span_id if empty or invalid span_id was received.\n\
    \\n\
    \ This field is required.\n\
    \\n\
    \\f\n\
    \\ENQ\EOT\ETX\STX\SOH\ENQ\DC2\ETXf\STX\a\n\
    \\f\n\
    \\ENQ\EOT\ETX\STX\SOH\SOH\DC2\ETXf\b\SI\n\
    \\f\n\
    \\ENQ\EOT\ETX\STX\SOH\ETX\DC2\ETXf\DC2\DC3\n\
    \\175\STX\n\
    \\EOT\EOT\ETX\STX\STX\DC2\ETXk\STX\EM\SUB\161\STX trace_state conveys information about request position in multiple distributed tracing graphs.\n\
    \ It is a trace_state in w3c-trace-context format: https://www.w3.org/TR/trace-context/#tracestate-header\n\
    \ See also https://github.com/w3c/distributed-tracing for more details about this field.\n\
    \\n\
    \\f\n\
    \\ENQ\EOT\ETX\STX\STX\ENQ\DC2\ETXk\STX\b\n\
    \\f\n\
    \\ENQ\EOT\ETX\STX\STX\SOH\DC2\ETXk\t\DC4\n\
    \\f\n\
    \\ENQ\EOT\ETX\STX\STX\ETX\DC2\ETXk\ETB\CAN\n\
    \\139\SOH\n\
    \\EOT\EOT\ETX\STX\ETX\DC2\ETXo\STX\ESC\SUB~ The `span_id` of this span's parent span. If this is a root span, then this\n\
    \ field must be empty. The ID is an 8-byte array.\n\
    \\n\
    \\f\n\
    \\ENQ\EOT\ETX\STX\ETX\ENQ\DC2\ETXo\STX\a\n\
    \\f\n\
    \\ENQ\EOT\ETX\STX\ETX\SOH\DC2\ETXo\b\SYN\n\
    \\f\n\
    \\ENQ\EOT\ETX\STX\ETX\ETX\DC2\ETXo\EM\SUB\n\
    \\218\ETX\n\
    \\EOT\EOT\ETX\STX\EOT\DC2\ETX|\STX\DC2\SUB\204\ETX A description of the span's operation.\n\
    \\n\
    \ For example, the name can be a qualified method name or a file name\n\
    \ and a line number where the operation is called. A best practice is to use\n\
    \ the same display name at the same call point in an application.\n\
    \ This makes it easier to correlate spans in different traces.\n\
    \\n\
    \ This field is semantically required to be set to non-empty string.\n\
    \ Empty value is equivalent to an unknown span name.\n\
    \\n\
    \ This field is required.\n\
    \\n\
    \\f\n\
    \\ENQ\EOT\ETX\STX\EOT\ENQ\DC2\ETX|\STX\b\n\
    \\f\n\
    \\ENQ\EOT\ETX\STX\EOT\SOH\DC2\ETX|\t\r\n\
    \\f\n\
    \\ENQ\EOT\ETX\STX\EOT\ETX\DC2\ETX|\DLE\DC1\n\
    \\155\SOH\n\
    \\EOT\EOT\ETX\EOT\NUL\DC2\ACK\128\SOH\STX\154\SOH\ETX\SUB\138\SOH SpanKind is the type of span. Can be used to specify additional relationships between spans\n\
    \ in addition to a parent/child relationship.\n\
    \\n\
    \\r\n\
    \\ENQ\EOT\ETX\EOT\NUL\SOH\DC2\EOT\128\SOH\a\SI\n\
    \\133\SOH\n\
    \\ACK\EOT\ETX\EOT\NUL\STX\NUL\DC2\EOT\131\SOH\EOT\RS\SUBu Unspecified. Do NOT use as default.\n\
    \ Implementations MAY assume SpanKind to be INTERNAL when receiving UNSPECIFIED.\n\
    \\n\
    \\SI\n\
    \\a\EOT\ETX\EOT\NUL\STX\NUL\SOH\DC2\EOT\131\SOH\EOT\EM\n\
    \\SI\n\
    \\a\EOT\ETX\EOT\NUL\STX\NUL\STX\DC2\EOT\131\SOH\FS\GS\n\
    \\170\SOH\n\
    \\ACK\EOT\ETX\EOT\NUL\STX\SOH\DC2\EOT\135\SOH\EOT\ESC\SUB\153\SOH Indicates that the span represents an internal operation within an application,\n\
    \ as opposed to an operation happening at the boundaries. Default value.\n\
    \\n\
    \\SI\n\
    \\a\EOT\ETX\EOT\NUL\STX\SOH\SOH\DC2\EOT\135\SOH\EOT\SYN\n\
    \\SI\n\
    \\a\EOT\ETX\EOT\NUL\STX\SOH\STX\DC2\EOT\135\SOH\EM\SUB\n\
    \q\n\
    \\ACK\EOT\ETX\EOT\NUL\STX\STX\DC2\EOT\139\SOH\EOT\EM\SUBa Indicates that the span covers server-side handling of an RPC or other\n\
    \ remote network request.\n\
    \\n\
    \\SI\n\
    \\a\EOT\ETX\EOT\NUL\STX\STX\SOH\DC2\EOT\139\SOH\EOT\DC4\n\
    \\SI\n\
    \\a\EOT\ETX\EOT\NUL\STX\STX\STX\DC2\EOT\139\SOH\ETB\CAN\n\
    \U\n\
    \\ACK\EOT\ETX\EOT\NUL\STX\ETX\DC2\EOT\142\SOH\EOT\EM\SUBE Indicates that the span describes a request to some remote service.\n\
    \\n\
    \\SI\n\
    \\a\EOT\ETX\EOT\NUL\STX\ETX\SOH\DC2\EOT\142\SOH\EOT\DC4\n\
    \\SI\n\
    \\a\EOT\ETX\EOT\NUL\STX\ETX\STX\DC2\EOT\142\SOH\ETB\CAN\n\
    \\232\STX\n\
    \\ACK\EOT\ETX\EOT\NUL\STX\EOT\DC2\EOT\148\SOH\EOT\ESC\SUB\215\STX Indicates that the span describes a producer sending a message to a broker.\n\
    \ Unlike CLIENT and SERVER, there is often no direct critical path latency relationship\n\
    \ between producer and consumer spans. A PRODUCER span ends when the message was accepted\n\
    \ by the broker while the logical processing of the message might span a much longer time.\n\
    \\n\
    \\SI\n\
    \\a\EOT\ETX\EOT\NUL\STX\EOT\SOH\DC2\EOT\148\SOH\EOT\SYN\n\
    \\SI\n\
    \\a\EOT\ETX\EOT\NUL\STX\EOT\STX\DC2\EOT\148\SOH\EM\SUB\n\
    \\219\SOH\n\
    \\ACK\EOT\ETX\EOT\NUL\STX\ENQ\DC2\EOT\153\SOH\EOT\ESC\SUB\202\SOH Indicates that the span describes consumer receiving a message from a broker.\n\
    \ Like the PRODUCER kind, there is often no direct critical path latency relationship\n\
    \ between producer and consumer spans.\n\
    \\n\
    \\SI\n\
    \\a\EOT\ETX\EOT\NUL\STX\ENQ\SOH\DC2\EOT\153\SOH\EOT\SYN\n\
    \\SI\n\
    \\a\EOT\ETX\EOT\NUL\STX\ENQ\STX\DC2\EOT\153\SOH\EM\SUB\n\
    \\245\SOH\n\
    \\EOT\EOT\ETX\STX\ENQ\DC2\EOT\159\SOH\STX\DC4\SUB\230\SOH Distinguishes between spans generated in a particular context. For example,\n\
    \ two spans with the same name may be distinguished using `CLIENT` (caller)\n\
    \ and `SERVER` (callee) to identify queueing latency associated with the span.\n\
    \\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\ENQ\ACK\DC2\EOT\159\SOH\STX\n\
    \\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\ENQ\SOH\DC2\EOT\159\SOH\v\SI\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\ENQ\ETX\DC2\EOT\159\SOH\DC2\DC3\n\
    \\166\ETX\n\
    \\EOT\EOT\ETX\STX\ACK\DC2\EOT\167\SOH\STX#\SUB\151\ETX start_time_unix_nano is the start time of the span. On the client side, this is the time\n\
    \ kept by the local machine where the span execution starts. On the server side, this\n\
    \ is the time when the server's application handler starts running.\n\
    \ Value is UNIX Epoch time in nanoseconds since 00:00:00 UTC on 1 January 1970.\n\
    \\n\
    \ This field is semantically required and it is expected that end_time >= start_time.\n\
    \\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\ACK\ENQ\DC2\EOT\167\SOH\STX\t\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\ACK\SOH\DC2\EOT\167\SOH\n\
    \\RS\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\ACK\ETX\DC2\EOT\167\SOH!\"\n\
    \\157\ETX\n\
    \\EOT\EOT\ETX\STX\a\DC2\EOT\175\SOH\STX!\SUB\142\ETX end_time_unix_nano is the end time of the span. On the client side, this is the time\n\
    \ kept by the local machine where the span execution ends. On the server side, this\n\
    \ is the time when the server application handler stops running.\n\
    \ Value is UNIX Epoch time in nanoseconds since 00:00:00 UTC on 1 January 1970.\n\
    \\n\
    \ This field is semantically required and it is expected that end_time >= start_time.\n\
    \\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\a\ENQ\DC2\EOT\175\SOH\STX\t\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\a\SOH\DC2\EOT\175\SOH\n\
    \\FS\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\a\ETX\DC2\EOT\175\SOH\US \n\
    \\220\EOT\n\
    \\EOT\EOT\ETX\STX\b\DC2\EOT\187\SOH\STXA\SUB\205\EOT attributes is a collection of key/value pairs. Note, global attributes\n\
    \ like server name can be set using the resource API. Examples of attributes:\n\
    \\n\
    \     \"/http/user_agent\": \"Mozilla/5.0 (Macintosh; Intel Mac OS X 10_14_2) AppleWebKit/537.36 (KHTML, like Gecko) Chrome/71.0.3578.98 Safari/537.36\"\n\
    \     \"/http/server_latency\": 300\n\
    \     \"abc.com/myattribute\": true\n\
    \     \"abc.com/score\": 10.239\n\
    \\n\
    \ The OpenTelemetry API specification further restricts the allowed value types:\n\
    \ https://github.com/open-telemetry/opentelemetry-specification/blob/main/specification/common/common.md#attributes\n\
    \\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\b\EOT\DC2\EOT\187\SOH\STX\n\
    \\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\b\ACK\DC2\EOT\187\SOH\v1\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\b\SOH\DC2\EOT\187\SOH2<\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\b\ETX\DC2\EOT\187\SOH?@\n\
    \\247\SOH\n\
    \\EOT\EOT\ETX\STX\t\DC2\EOT\192\SOH\STX'\SUB\232\SOH dropped_attributes_count is the number of attributes that were discarded. Attributes\n\
    \ can be discarded because their keys are too long or because there are too many\n\
    \ attributes. If this value is 0, then no attributes were dropped.\n\
    \\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\t\ENQ\DC2\EOT\192\SOH\STX\b\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\t\SOH\DC2\EOT\192\SOH\t!\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\t\ETX\DC2\EOT\192\SOH$&\n\
    \\132\SOH\n\
    \\EOT\EOT\ETX\ETX\NUL\DC2\ACK\196\SOH\STX\210\SOH\ETX\SUBt Event is a time-stamped annotation of the span, consisting of user-supplied\n\
    \ text description and key-value pairs.\n\
    \\n\
    \\r\n\
    \\ENQ\EOT\ETX\ETX\NUL\SOH\DC2\EOT\196\SOH\n\
    \\SI\n\
    \@\n\
    \\ACK\EOT\ETX\ETX\NUL\STX\NUL\DC2\EOT\198\SOH\EOT\US\SUB0 time_unix_nano is the time the event occurred.\n\
    \\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\NUL\STX\NUL\ENQ\DC2\EOT\198\SOH\EOT\v\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\NUL\STX\NUL\SOH\DC2\EOT\198\SOH\f\SUB\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\NUL\STX\NUL\ETX\DC2\EOT\198\SOH\GS\RS\n\
    \h\n\
    \\ACK\EOT\ETX\ETX\NUL\STX\SOH\DC2\EOT\202\SOH\EOT\DC4\SUBX name of the event.\n\
    \ This field is semantically required to be set to non-empty string.\n\
    \\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\NUL\STX\SOH\ENQ\DC2\EOT\202\SOH\EOT\n\
    \\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\NUL\STX\SOH\SOH\DC2\EOT\202\SOH\v\SI\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\NUL\STX\SOH\ETX\DC2\EOT\202\SOH\DC2\DC3\n\
    \W\n\
    \\ACK\EOT\ETX\ETX\NUL\STX\STX\DC2\EOT\205\SOH\EOTC\SUBG attributes is a collection of attribute key/value pairs on the event.\n\
    \\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\NUL\STX\STX\EOT\DC2\EOT\205\SOH\EOT\f\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\NUL\STX\STX\ACK\DC2\EOT\205\SOH\r3\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\NUL\STX\STX\SOH\DC2\EOT\205\SOH4>\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\NUL\STX\STX\ETX\DC2\EOT\205\SOHAB\n\
    \\132\SOH\n\
    \\ACK\EOT\ETX\ETX\NUL\STX\ETX\DC2\EOT\209\SOH\EOT(\SUBt dropped_attributes_count is the number of dropped attributes. If the value is 0,\n\
    \ then no attributes were dropped.\n\
    \\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\NUL\STX\ETX\ENQ\DC2\EOT\209\SOH\EOT\n\
    \\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\NUL\STX\ETX\SOH\DC2\EOT\209\SOH\v#\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\NUL\STX\ETX\ETX\DC2\EOT\209\SOH&'\n\
    \6\n\
    \\EOT\EOT\ETX\STX\n\
    \\DC2\EOT\213\SOH\STX\GS\SUB( events is a collection of Event items.\n\
    \\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\n\
    \\EOT\DC2\EOT\213\SOH\STX\n\
    \\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\n\
    \\ACK\DC2\EOT\213\SOH\v\DLE\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\n\
    \\SOH\DC2\EOT\213\SOH\DC1\ETB\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\n\
    \\ETX\DC2\EOT\213\SOH\SUB\FS\n\
    \v\n\
    \\EOT\EOT\ETX\STX\v\DC2\EOT\217\SOH\STX#\SUBh dropped_events_count is the number of dropped events. If the value is 0, then no\n\
    \ events were dropped.\n\
    \\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\v\ENQ\DC2\EOT\217\SOH\STX\b\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\v\SOH\DC2\EOT\217\SOH\t\GS\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\v\ETX\DC2\EOT\217\SOH \"\n\
    \\182\STX\n\
    \\EOT\EOT\ETX\ETX\SOH\DC2\ACK\223\SOH\STX\240\SOH\ETX\SUB\165\STX A pointer from the current span to another span in the same trace or in a\n\
    \ different trace. For example, this can be used in batching operations,\n\
    \ where a single batch handler processes multiple requests from different\n\
    \ traces or when the handler receives a request from a different project.\n\
    \\n\
    \\r\n\
    \\ENQ\EOT\ETX\ETX\SOH\SOH\DC2\EOT\223\SOH\n\
    \\SO\n\
    \n\n\
    \\ACK\EOT\ETX\ETX\SOH\STX\NUL\DC2\EOT\226\SOH\EOT\ETB\SUB^ A unique identifier of a trace that this linked span is part of. The ID is a\n\
    \ 16-byte array.\n\
    \\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\SOH\STX\NUL\ENQ\DC2\EOT\226\SOH\EOT\t\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\SOH\STX\NUL\SOH\DC2\EOT\226\SOH\n\
    \\DC2\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\SOH\STX\NUL\ETX\DC2\EOT\226\SOH\NAK\SYN\n\
    \U\n\
    \\ACK\EOT\ETX\ETX\SOH\STX\SOH\DC2\EOT\229\SOH\EOT\SYN\SUBE A unique identifier for the linked span. The ID is an 8-byte array.\n\
    \\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\SOH\STX\SOH\ENQ\DC2\EOT\229\SOH\EOT\t\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\SOH\STX\SOH\SOH\DC2\EOT\229\SOH\n\
    \\DC1\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\SOH\STX\SOH\ETX\DC2\EOT\229\SOH\DC4\NAK\n\
    \;\n\
    \\ACK\EOT\ETX\ETX\SOH\STX\STX\DC2\EOT\232\SOH\EOT\ESC\SUB+ The trace_state associated with the link.\n\
    \\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\SOH\STX\STX\ENQ\DC2\EOT\232\SOH\EOT\n\
    \\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\SOH\STX\STX\SOH\DC2\EOT\232\SOH\v\SYN\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\SOH\STX\STX\ETX\DC2\EOT\232\SOH\EM\SUB\n\
    \V\n\
    \\ACK\EOT\ETX\ETX\SOH\STX\ETX\DC2\EOT\235\SOH\EOTC\SUBF attributes is a collection of attribute key/value pairs on the link.\n\
    \\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\SOH\STX\ETX\EOT\DC2\EOT\235\SOH\EOT\f\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\SOH\STX\ETX\ACK\DC2\EOT\235\SOH\r3\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\SOH\STX\ETX\SOH\DC2\EOT\235\SOH4>\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\SOH\STX\ETX\ETX\DC2\EOT\235\SOHAB\n\
    \\132\SOH\n\
    \\ACK\EOT\ETX\ETX\SOH\STX\EOT\DC2\EOT\239\SOH\EOT(\SUBt dropped_attributes_count is the number of dropped attributes. If the value is 0,\n\
    \ then no attributes were dropped.\n\
    \\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\SOH\STX\EOT\ENQ\DC2\EOT\239\SOH\EOT\n\
    \\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\SOH\STX\EOT\SOH\DC2\EOT\239\SOH\v#\n\
    \\SI\n\
    \\a\EOT\ETX\ETX\SOH\STX\EOT\ETX\DC2\EOT\239\SOH&'\n\
    \~\n\
    \\EOT\EOT\ETX\STX\f\DC2\EOT\244\SOH\STX\ESC\SUBp links is a collection of Links, which are references from this span to a span\n\
    \ in the same or different trace.\n\
    \\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\f\EOT\DC2\EOT\244\SOH\STX\n\
    \\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\f\ACK\DC2\EOT\244\SOH\v\SI\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\f\SOH\DC2\EOT\244\SOH\DLE\NAK\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\f\ETX\DC2\EOT\244\SOH\CAN\SUB\n\
    \\153\SOH\n\
    \\EOT\EOT\ETX\STX\r\DC2\EOT\248\SOH\STX\"\SUB\138\SOH dropped_links_count is the number of dropped links after the maximum size was\n\
    \ enforced. If this value is 0, then no links were dropped.\n\
    \\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\r\ENQ\DC2\EOT\248\SOH\STX\b\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\r\SOH\DC2\EOT\248\SOH\t\FS\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\r\ETX\DC2\EOT\248\SOH\US!\n\
    \\173\SOH\n\
    \\EOT\EOT\ETX\STX\SO\DC2\EOT\252\SOH\STX\NAK\SUB\158\SOH An optional final status for this span. Semantically when Status isn't set, it means\n\
    \ span's status code is unset, i.e. assume STATUS_CODE_UNSET (code = 0).\n\
    \\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\SO\ACK\DC2\EOT\252\SOH\STX\b\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\SO\SOH\DC2\EOT\252\SOH\t\SI\n\
    \\r\n\
    \\ENQ\EOT\ETX\STX\SO\ETX\DC2\EOT\252\SOH\DC2\DC4\n\
    \\145\SO\n\
    \\STX\EOT\EOT\DC2\ACK\129\STX\NUL\214\STX\SOH\SUB\139\SOH The Status type defines a logical error model that is suitable for different\n\
    \ programming environments, including REST APIs and RPC APIs.\n\
    \\"\244\f IMPORTANT: Backward compatibility notes:\n\
    \\n\
    \ To ensure any pair of senders and receivers continues to correctly signal and\n\
    \ interpret erroneous situations, the senders and receivers MUST follow these rules:\n\
    \\n\
    \ 1. Old senders and receivers that are not aware of `code` field will continue using\n\
    \ the `deprecated_code` field to signal and interpret erroneous situation.\n\
    \\n\
    \ 2. New senders, which are aware of the `code` field MUST set both the\n\
    \ `deprecated_code` and `code` fields according to the following rules:\n\
    \\n\
    \   if code==STATUS_CODE_UNSET then `deprecated_code` MUST be\n\
    \   set to DEPRECATED_STATUS_CODE_OK.\n\
    \\n\
    \   if code==STATUS_CODE_OK then `deprecated_code` MUST be\n\
    \   set to DEPRECATED_STATUS_CODE_OK.\n\
    \\n\
    \   if code==STATUS_CODE_ERROR then `deprecated_code` MUST be\n\
    \   set to DEPRECATED_STATUS_CODE_UNKNOWN_ERROR.\n\
    \\n\
    \ These rules allow old receivers to correctly interpret data received from new senders.\n\
    \\n\
    \ 3. New receivers MUST look at both the `code` and `deprecated_code` fields in order\n\
    \ to interpret the overall status:\n\
    \\n\
    \   If code==STATUS_CODE_UNSET then the value of `deprecated_code` is the\n\
    \   carrier of the overall status according to these rules:\n\
    \\n\
    \     if deprecated_code==DEPRECATED_STATUS_CODE_OK then the receiver MUST interpret\n\
    \     the overall status to be STATUS_CODE_UNSET.\n\
    \\n\
    \     if deprecated_code!=DEPRECATED_STATUS_CODE_OK then the receiver MUST interpret\n\
    \     the overall status to be STATUS_CODE_ERROR.\n\
    \\n\
    \   If code!=STATUS_CODE_UNSET then the value of `deprecated_code` MUST be\n\
    \   ignored, the `code` field is the sole carrier of the status.\n\
    \\n\
    \ These rules allow new receivers to correctly interpret data received from old senders.\n\
    \\n\
    \\v\n\
    \\ETX\EOT\EOT\SOH\DC2\EOT\129\STX\b\SO\n\
    \\SO\n\
    \\EOT\EOT\EOT\EOT\NUL\DC2\ACK\169\STX\STX\187\STX\ETX\n\
    \\r\n\
    \\ENQ\EOT\EOT\EOT\NUL\SOH\DC2\EOT\169\STX\a\ESC\n\
    \\SO\n\
    \\ACK\EOT\EOT\EOT\NUL\STX\NUL\DC2\EOT\170\STX\EOT3\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\NUL\SOH\DC2\EOT\170\STX\EOT\GS\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\NUL\STX\DC2\EOT\170\STX12\n\
    \\SO\n\
    \\ACK\EOT\EOT\EOT\NUL\STX\SOH\DC2\EOT\171\STX\EOT3\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\SOH\SOH\DC2\EOT\171\STX\EOT$\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\SOH\STX\DC2\EOT\171\STX12\n\
    \\SO\n\
    \\ACK\EOT\EOT\EOT\NUL\STX\STX\DC2\EOT\172\STX\EOT3\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\STX\SOH\DC2\EOT\172\STX\EOT(\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\STX\STX\DC2\EOT\172\STX12\n\
    \\SO\n\
    \\ACK\EOT\EOT\EOT\NUL\STX\ETX\DC2\EOT\173\STX\EOT3\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\ETX\SOH\DC2\EOT\173\STX\EOT+\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\ETX\STX\DC2\EOT\173\STX12\n\
    \\SO\n\
    \\ACK\EOT\EOT\EOT\NUL\STX\EOT\DC2\EOT\174\STX\EOT3\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\EOT\SOH\DC2\EOT\174\STX\EOT,\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\EOT\STX\DC2\EOT\174\STX12\n\
    \\SO\n\
    \\ACK\EOT\EOT\EOT\NUL\STX\ENQ\DC2\EOT\175\STX\EOT3\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\ENQ\SOH\DC2\EOT\175\STX\EOT$\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\ENQ\STX\DC2\EOT\175\STX12\n\
    \\SO\n\
    \\ACK\EOT\EOT\EOT\NUL\STX\ACK\DC2\EOT\176\STX\EOT3\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\ACK\SOH\DC2\EOT\176\STX\EOT)\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\ACK\STX\DC2\EOT\176\STX12\n\
    \\SO\n\
    \\ACK\EOT\EOT\EOT\NUL\STX\a\DC2\EOT\177\STX\EOT3\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\a\SOH\DC2\EOT\177\STX\EOT,\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\a\STX\DC2\EOT\177\STX12\n\
    \\SO\n\
    \\ACK\EOT\EOT\EOT\NUL\STX\b\DC2\EOT\178\STX\EOT3\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\b\SOH\DC2\EOT\178\STX\EOT-\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\b\STX\DC2\EOT\178\STX12\n\
    \\SO\n\
    \\ACK\EOT\EOT\EOT\NUL\STX\t\DC2\EOT\179\STX\EOT3\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\t\SOH\DC2\EOT\179\STX\EOT.\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\t\STX\DC2\EOT\179\STX12\n\
    \\SO\n\
    \\ACK\EOT\EOT\EOT\NUL\STX\n\
    \\DC2\EOT\180\STX\EOT4\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\n\
    \\SOH\DC2\EOT\180\STX\EOT\"\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\n\
    \\STX\DC2\EOT\180\STX13\n\
    \\SO\n\
    \\ACK\EOT\EOT\EOT\NUL\STX\v\DC2\EOT\181\STX\EOT4\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\v\SOH\DC2\EOT\181\STX\EOT'\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\v\STX\DC2\EOT\181\STX13\n\
    \\SO\n\
    \\ACK\EOT\EOT\EOT\NUL\STX\f\DC2\EOT\182\STX\EOT4\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\f\SOH\DC2\EOT\182\STX\EOT(\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\f\STX\DC2\EOT\182\STX13\n\
    \\SO\n\
    \\ACK\EOT\EOT\EOT\NUL\STX\r\DC2\EOT\183\STX\EOT4\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\r\SOH\DC2\EOT\183\STX\EOT)\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\r\STX\DC2\EOT\183\STX13\n\
    \\SO\n\
    \\ACK\EOT\EOT\EOT\NUL\STX\SO\DC2\EOT\184\STX\EOT4\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\SO\SOH\DC2\EOT\184\STX\EOT&\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\SO\STX\DC2\EOT\184\STX13\n\
    \\SO\n\
    \\ACK\EOT\EOT\EOT\NUL\STX\SI\DC2\EOT\185\STX\EOT4\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\SI\SOH\DC2\EOT\185\STX\EOT$\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\SI\STX\DC2\EOT\185\STX13\n\
    \\SO\n\
    \\ACK\EOT\EOT\EOT\NUL\STX\DLE\DC2\EOT\186\STX\EOT4\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\DLE\SOH\DC2\EOT\186\STX\EOT*\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\NUL\STX\DLE\STX\DC2\EOT\186\STX13\n\
    \\131\ETX\n\
    \\EOT\EOT\EOT\STX\NUL\DC2\EOT\195\STX\STX=\SUB\244\STX The deprecated status code. This is an optional field.\n\
    \\n\
    \ This field is deprecated and is replaced by the `code` field below. See backward\n\
    \ compatibility notes below. According to our stability guarantees this field\n\
    \ will be removed in 12 months, on Oct 22, 2021. All usage of old senders and\n\
    \ receivers that do not understand the `code` field MUST be phased out by then.\n\
    \\n\
    \\r\n\
    \\ENQ\EOT\EOT\STX\NUL\ACK\DC2\EOT\195\STX\STX\SYN\n\
    \\r\n\
    \\ENQ\EOT\EOT\STX\NUL\SOH\DC2\EOT\195\STX\ETB&\n\
    \\r\n\
    \\ENQ\EOT\EOT\STX\NUL\ETX\DC2\EOT\195\STX)*\n\
    \\r\n\
    \\ENQ\EOT\EOT\STX\NUL\b\DC2\EOT\195\STX+<\n\
    \\SO\n\
    \\ACK\EOT\EOT\STX\NUL\b\ETX\DC2\EOT\195\STX,;\n\
    \@\n\
    \\EOT\EOT\EOT\STX\SOH\DC2\EOT\198\STX\STX\NAK\SUB2 A developer-facing human readable error message.\n\
    \\n\
    \\r\n\
    \\ENQ\EOT\EOT\STX\SOH\ENQ\DC2\EOT\198\STX\STX\b\n\
    \\r\n\
    \\ENQ\EOT\EOT\STX\SOH\SOH\DC2\EOT\198\STX\t\DLE\n\
    \\r\n\
    \\ENQ\EOT\EOT\STX\SOH\ETX\DC2\EOT\198\STX\DC3\DC4\n\
    \\167\SOH\n\
    \\EOT\EOT\EOT\EOT\SOH\DC2\ACK\202\STX\STX\210\STX\ETX\SUB\150\SOH For the semantics of status codes see\n\
    \ https://github.com/open-telemetry/opentelemetry-specification/blob/main/specification/trace/api.md#set-status\n\
    \\n\
    \\r\n\
    \\ENQ\EOT\EOT\EOT\SOH\SOH\DC2\EOT\202\STX\a\DC1\n\
    \%\n\
    \\ACK\EOT\EOT\EOT\SOH\STX\NUL\DC2\EOT\204\STX\EOT(\SUB\NAK The default status.\n\
    \\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\SOH\STX\NUL\SOH\DC2\EOT\204\STX\EOT\NAK\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\SOH\STX\NUL\STX\DC2\EOT\204\STX&'\n\
    \w\n\
    \\ACK\EOT\EOT\EOT\SOH\STX\SOH\DC2\EOT\207\STX\EOT(\SUBg The Span has been validated by an Application developers or Operator to have\n\
    \ completed successfully.\n\
    \\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\SOH\STX\SOH\SOH\DC2\EOT\207\STX\EOT\DC2\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\SOH\STX\SOH\STX\DC2\EOT\207\STX&'\n\
    \-\n\
    \\ACK\EOT\EOT\EOT\SOH\STX\STX\DC2\EOT\209\STX\EOT(\SUB\GS The Span contains an error.\n\
    \\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\SOH\STX\STX\SOH\DC2\EOT\209\STX\EOT\NAK\n\
    \\SI\n\
    \\a\EOT\EOT\EOT\SOH\STX\STX\STX\DC2\EOT\209\STX&'\n\
    \ \n\
    \\EOT\EOT\EOT\STX\STX\DC2\EOT\213\STX\STX\SYN\SUB\DC2 The status code.\n\
    \\n\
    \\r\n\
    \\ENQ\EOT\EOT\STX\STX\ACK\DC2\EOT\213\STX\STX\f\n\
    \\r\n\
    \\ENQ\EOT\EOT\STX\STX\SOH\DC2\EOT\213\STX\r\DC1\n\
    \\r\n\
    \\ENQ\EOT\EOT\STX\STX\ETX\DC2\EOT\213\STX\DC4\NAKb\ACKproto3"