module Patrol.Type.TraceContext where

import qualified Data.Aeson as Aeson
import qualified Data.Text as Text
import qualified Patrol.Extra.Aeson as Aeson
import qualified Patrol.Type.SpanStatus as SpanStatus

-- | <https://develop.sentry.dev/sdk/event-payloads/types/#tracecontext>
data TraceContext = TraceContext
  { TraceContext -> Maybe Int
exclusiveTime :: Maybe Int,
    TraceContext -> Text
op :: Text.Text,
    TraceContext -> Text
parentSpanId :: Text.Text,
    TraceContext -> Text
spanId :: Text.Text,
    TraceContext -> Maybe SpanStatus
status :: Maybe SpanStatus.SpanStatus,
    TraceContext -> Text
traceId :: Text.Text
  }
  deriving (TraceContext -> TraceContext -> Bool
(TraceContext -> TraceContext -> Bool)
-> (TraceContext -> TraceContext -> Bool) -> Eq TraceContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TraceContext -> TraceContext -> Bool
== :: TraceContext -> TraceContext -> Bool
$c/= :: TraceContext -> TraceContext -> Bool
/= :: TraceContext -> TraceContext -> Bool
Eq, Int -> TraceContext -> ShowS
[TraceContext] -> ShowS
TraceContext -> String
(Int -> TraceContext -> ShowS)
-> (TraceContext -> String)
-> ([TraceContext] -> ShowS)
-> Show TraceContext
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TraceContext -> ShowS
showsPrec :: Int -> TraceContext -> ShowS
$cshow :: TraceContext -> String
show :: TraceContext -> String
$cshowList :: [TraceContext] -> ShowS
showList :: [TraceContext] -> ShowS
Show)

instance Aeson.ToJSON TraceContext where
  toJSON :: TraceContext -> Value
toJSON TraceContext
traceContext =
    [Pair] -> Value
Aeson.intoObject
      [ String -> Maybe Int -> Pair
forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"exclusive_time" (Maybe Int -> Pair) -> Maybe Int -> Pair
forall a b. (a -> b) -> a -> b
$ TraceContext -> Maybe Int
exclusiveTime TraceContext
traceContext,
        String -> Text -> Pair
forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"op" (Text -> Pair) -> Text -> Pair
forall a b. (a -> b) -> a -> b
$ TraceContext -> Text
op TraceContext
traceContext,
        String -> Text -> Pair
forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"parent_span_id" (Text -> Pair) -> Text -> Pair
forall a b. (a -> b) -> a -> b
$ TraceContext -> Text
parentSpanId TraceContext
traceContext,
        String -> Text -> Pair
forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"span_id" (Text -> Pair) -> Text -> Pair
forall a b. (a -> b) -> a -> b
$ TraceContext -> Text
spanId TraceContext
traceContext,
        String -> Maybe SpanStatus -> Pair
forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"status" (Maybe SpanStatus -> Pair) -> Maybe SpanStatus -> Pair
forall a b. (a -> b) -> a -> b
$ TraceContext -> Maybe SpanStatus
status TraceContext
traceContext,
        String -> Text -> Pair
forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"trace_id" (Text -> Pair) -> Text -> Pair
forall a b. (a -> b) -> a -> b
$ TraceContext -> Text
traceId TraceContext
traceContext
      ]

empty :: TraceContext
empty :: TraceContext
empty =
  TraceContext
    { exclusiveTime :: Maybe Int
exclusiveTime = Maybe Int
forall a. Maybe a
Nothing,
      op :: Text
op = Text
Text.empty,
      parentSpanId :: Text
parentSpanId = Text
Text.empty,
      spanId :: Text
spanId = Text
Text.empty,
      status :: Maybe SpanStatus
status = Maybe SpanStatus
forall a. Maybe a
Nothing,
      traceId :: Text
traceId = Text
Text.empty
    }