{-# LANGUAGE DeriveGeneric     #-}
{-# LANGUAGE OverloadedStrings #-}
{-|
Module      : Instana.SDK.TracingHeaders
Description : A set of tracing headers
-}
module Instana.SDK.TracingHeaders
  ( TracingHeaders(..)
  , TracingLevel(..)
  , levelHeaderName
  , maybeStringToTracingLevel
  , spanIdHeaderName
  , stringToTracingLevel
  , traceIdHeaderName
  , tracingLevelToString
  ) where


import           GHC.Generics
import qualified Network.HTTP.Types.Header as HTTPHeader


-- |X-INSTANA-T
traceIdHeaderName :: HTTPHeader.HeaderName
traceIdHeaderName :: HeaderName
traceIdHeaderName = "X-INSTANA-T"


-- |X-INSTANA-S
spanIdHeaderName :: HTTPHeader.HeaderName
spanIdHeaderName :: HeaderName
spanIdHeaderName = "X-INSTANA-S"


-- |X-INSTANA-L
levelHeaderName :: HTTPHeader.HeaderName
levelHeaderName :: HeaderName
levelHeaderName = "X-INSTANA-L"


-- |Tracing level.
data TracingLevel =
    -- |Record calls.
    Trace
    -- |Don't record calls.
  | Suppress
  deriving (TracingLevel -> TracingLevel -> Bool
(TracingLevel -> TracingLevel -> Bool)
-> (TracingLevel -> TracingLevel -> Bool) -> Eq TracingLevel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TracingLevel -> TracingLevel -> Bool
$c/= :: TracingLevel -> TracingLevel -> Bool
== :: TracingLevel -> TracingLevel -> Bool
$c== :: TracingLevel -> TracingLevel -> Bool
Eq, (forall x. TracingLevel -> Rep TracingLevel x)
-> (forall x. Rep TracingLevel x -> TracingLevel)
-> Generic TracingLevel
forall x. Rep TracingLevel x -> TracingLevel
forall x. TracingLevel -> Rep TracingLevel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TracingLevel x -> TracingLevel
$cfrom :: forall x. TracingLevel -> Rep TracingLevel x
Generic, Int -> TracingLevel -> ShowS
[TracingLevel] -> ShowS
TracingLevel -> String
(Int -> TracingLevel -> ShowS)
-> (TracingLevel -> String)
-> ([TracingLevel] -> ShowS)
-> Show TracingLevel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TracingLevel] -> ShowS
$cshowList :: [TracingLevel] -> ShowS
show :: TracingLevel -> String
$cshow :: TracingLevel -> String
showsPrec :: Int -> TracingLevel -> ShowS
$cshowsPrec :: Int -> TracingLevel -> ShowS
Show)


-- |Converts a string into the tracing level.
stringToTracingLevel :: String -> TracingLevel
stringToTracingLevel :: String -> TracingLevel
stringToTracingLevel s :: String
s =
  if String
s String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== "0" then TracingLevel
Suppress else TracingLevel
Trace


-- |Converts a string into the tracing level.
maybeStringToTracingLevel :: Maybe String -> TracingLevel
maybeStringToTracingLevel :: Maybe String -> TracingLevel
maybeStringToTracingLevel s :: Maybe String
s =
  if Maybe String
s Maybe String -> Maybe String -> Bool
forall a. Eq a => a -> a -> Bool
== String -> Maybe String
forall a. a -> Maybe a
Just "0" then TracingLevel
Suppress else TracingLevel
Trace


-- |Converts tracing level into a string.
tracingLevelToString :: TracingLevel -> String
tracingLevelToString :: TracingLevel -> String
tracingLevelToString l :: TracingLevel
l =
  case TracingLevel
l of
    Trace    -> "1"
    Suppress -> "0"


-- |A set of tracing headers.
data TracingHeaders  =
  TracingHeaders
    {
      -- |the trace ID
      TracingHeaders -> Maybe String
traceId :: Maybe String
      -- |the span ID
    , TracingHeaders -> Maybe String
spanId  :: Maybe String
      -- |the tracing level (on/off)
    , TracingHeaders -> TracingLevel
level   :: TracingLevel
    } deriving (TracingHeaders -> TracingHeaders -> Bool
(TracingHeaders -> TracingHeaders -> Bool)
-> (TracingHeaders -> TracingHeaders -> Bool) -> Eq TracingHeaders
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TracingHeaders -> TracingHeaders -> Bool
$c/= :: TracingHeaders -> TracingHeaders -> Bool
== :: TracingHeaders -> TracingHeaders -> Bool
$c== :: TracingHeaders -> TracingHeaders -> Bool
Eq, (forall x. TracingHeaders -> Rep TracingHeaders x)
-> (forall x. Rep TracingHeaders x -> TracingHeaders)
-> Generic TracingHeaders
forall x. Rep TracingHeaders x -> TracingHeaders
forall x. TracingHeaders -> Rep TracingHeaders x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TracingHeaders x -> TracingHeaders
$cfrom :: forall x. TracingHeaders -> Rep TracingHeaders x
Generic, Int -> TracingHeaders -> ShowS
[TracingHeaders] -> ShowS
TracingHeaders -> String
(Int -> TracingHeaders -> ShowS)
-> (TracingHeaders -> String)
-> ([TracingHeaders] -> ShowS)
-> Show TracingHeaders
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TracingHeaders] -> ShowS
$cshowList :: [TracingHeaders] -> ShowS
show :: TracingHeaders -> String
$cshow :: TracingHeaders -> String
showsPrec :: Int -> TracingHeaders -> ShowS
$cshowsPrec :: Int -> TracingHeaders -> ShowS
Show)