{-# LANGUAGE DeriveGeneric #-}
{-|
Module      : Instana.SDK.Span.RootEntry
Description : A root entry span
-}
module Instana.SDK.Span.RootEntry
  ( RootEntry(..)
  , spanId
  , traceId
  , addData
  , addToErrorCount
  , setServiceName
  , setCorrelationType
  , setCorrelationId
  , setSynthetic
  , setW3cTraceContext
  ) where


import           Data.Aeson                           (Value)
import qualified Data.Aeson.Extra.Merge               as AesonExtra
import           Data.Text                            (Text)
import           GHC.Generics

import           Instana.SDK.Internal.Id              (Id)
import           Instana.SDK.Internal.W3CTraceContext (W3CTraceContext)


-- |An entry span that is the root span of a trace.
data RootEntry =
  RootEntry
    {
      -- |The trace ID and span ID (those are identical for root spans)
      RootEntry -> Id
spanAndTraceId  :: Id
      -- |The span name/type, e.g. a short string like "haskell.wai.server",
      -- "haskell.http.client". For SDK spans this is always "sdk", the actual
      -- name is then in span.data.sdk.name.
    , RootEntry -> Text
spanName        :: Text
      -- |The time the span (and trace) started
    , RootEntry -> Int
timestamp       :: Int
      -- |The number of errors that occured during processing
    , RootEntry -> Int
errorCount      :: Int
      -- |An attribute for overriding the name of the service in Instana
    , RootEntry -> Maybe Text
serviceName     :: Maybe Text
      -- |A flag indicating that this span represents a synthetic call
    , RootEntry -> Bool
synthetic       :: Bool
      -- |The website monitoring correlation type
    , RootEntry -> Maybe Text
correlationType :: Maybe Text
      -- |The website monitoring correlation ID
    , RootEntry -> Maybe Text
correlationId   :: Maybe Text
      -- |Additional data for the span. Must be provided as an
      -- 'Data.Aeson.Value'.
    , RootEntry -> Value
spanData        :: Value
      -- |The W3C Trace Context. An entry span only has an associated W3C trace
      -- context, if W3C trace context headers have been received.
    , RootEntry -> Maybe W3CTraceContext
w3cTraceContext :: Maybe W3CTraceContext

    } deriving (RootEntry -> RootEntry -> Bool
(RootEntry -> RootEntry -> Bool)
-> (RootEntry -> RootEntry -> Bool) -> Eq RootEntry
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RootEntry -> RootEntry -> Bool
$c/= :: RootEntry -> RootEntry -> Bool
== :: RootEntry -> RootEntry -> Bool
$c== :: RootEntry -> RootEntry -> Bool
Eq, (forall x. RootEntry -> Rep RootEntry x)
-> (forall x. Rep RootEntry x -> RootEntry) -> Generic RootEntry
forall x. Rep RootEntry x -> RootEntry
forall x. RootEntry -> Rep RootEntry x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RootEntry x -> RootEntry
$cfrom :: forall x. RootEntry -> Rep RootEntry x
Generic, Int -> RootEntry -> ShowS
[RootEntry] -> ShowS
RootEntry -> String
(Int -> RootEntry -> ShowS)
-> (RootEntry -> String)
-> ([RootEntry] -> ShowS)
-> Show RootEntry
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RootEntry] -> ShowS
$cshowList :: [RootEntry] -> ShowS
show :: RootEntry -> String
$cshow :: RootEntry -> String
showsPrec :: Int -> RootEntry -> ShowS
$cshowsPrec :: Int -> RootEntry -> ShowS
Show)


-- |Accessor for the trace ID.
traceId :: RootEntry -> Id
traceId :: RootEntry -> Id
traceId = RootEntry -> Id
spanAndTraceId


-- |Accessor for the span ID.
spanId :: RootEntry -> Id
spanId :: RootEntry -> Id
spanId = RootEntry -> Id
spanAndTraceId


-- |Add to the error count.
addToErrorCount :: Int -> RootEntry -> RootEntry
addToErrorCount :: Int -> RootEntry -> RootEntry
addToErrorCount increment :: Int
increment rootEntry :: RootEntry
rootEntry =
  let
    ec :: Int
ec = RootEntry -> Int
errorCount RootEntry
rootEntry
  in
  RootEntry
rootEntry { errorCount :: Int
errorCount = Int
ec Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
increment }


-- |Override the name of the service for the associated call in Instana.
setServiceName :: Text -> RootEntry -> RootEntry
setServiceName :: Text -> RootEntry -> RootEntry
setServiceName serviceName_ :: Text
serviceName_ rootEntry :: RootEntry
rootEntry =
  RootEntry
rootEntry { serviceName :: Maybe Text
serviceName = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
serviceName_ }


-- |Attaches a W3C trace context to the span.
setW3cTraceContext :: W3CTraceContext -> RootEntry -> RootEntry
setW3cTraceContext :: W3CTraceContext -> RootEntry -> RootEntry
setW3cTraceContext w3cTraceContext_ :: W3CTraceContext
w3cTraceContext_ rootEntry :: RootEntry
rootEntry =
  RootEntry
rootEntry { w3cTraceContext :: Maybe W3CTraceContext
w3cTraceContext = W3CTraceContext -> Maybe W3CTraceContext
forall a. a -> Maybe a
Just W3CTraceContext
w3cTraceContext_ }


-- |Set the synthetic flag.
setSynthetic :: Bool -> RootEntry -> RootEntry
setSynthetic :: Bool -> RootEntry -> RootEntry
setSynthetic synthetic_ :: Bool
synthetic_ rootEntry :: RootEntry
rootEntry =
  RootEntry
rootEntry { synthetic :: Bool
synthetic = Bool
synthetic_ }


-- |Set the website monitoring correlation type.
setCorrelationType :: Text -> RootEntry -> RootEntry
setCorrelationType :: Text -> RootEntry -> RootEntry
setCorrelationType correlationType_ :: Text
correlationType_ rootEntry :: RootEntry
rootEntry =
  RootEntry
rootEntry { correlationType :: Maybe Text
correlationType = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
correlationType_ }


-- |Set the website monitoring correlation ID.
setCorrelationId :: Text -> RootEntry -> RootEntry
setCorrelationId :: Text -> RootEntry -> RootEntry
setCorrelationId correlationId_ :: Text
correlationId_ rootEntry :: RootEntry
rootEntry =
  RootEntry
rootEntry { correlationId :: Maybe Text
correlationId = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
correlationId_ }


-- |Add a value to the span's data section.
addData :: Value -> RootEntry -> RootEntry
addData :: Value -> RootEntry -> RootEntry
addData newData :: Value
newData rootEntry :: RootEntry
rootEntry =
  let
    currentData :: Value
currentData = RootEntry -> Value
spanData RootEntry
rootEntry
    mergedData :: Value
mergedData = Value -> Value -> Value
AesonExtra.lodashMerge Value
currentData Value
newData
  in
  RootEntry
rootEntry { spanData :: Value
spanData = Value
mergedData }