-----------------------------------------------------------------------------

-----------------------------------------------------------------------------

{- |
 Module      :  OpenTelemetry.Trace.TraceState
 Copyright   :  (c) Ian Duncan, 2021
 License     :  BSD-3
 Description :  W3C-compliant way to provide additional vendor-specific trace identification information across different distributed tracing systems
 Maintainer  :  Ian Duncan
 Stability   :  experimental
 Portability :  non-portable (GHC extensions)

 The main purpose of the tracestate HTTP header is to provide additional vendor-specific trace identification information across different distributed tracing systems and is a companion header for the traceparent field. It also conveys information about the request’s position in multiple distributed tracing graphs.

 The tracestate field may contain any opaque value in any of the keys. Tracestate MAY be sent or received as multiple header fields. Multiple tracestate header fields MUST be handled as specified by RFC7230 Section 3.2.2 Field Order. The tracestate header SHOULD be sent as a single field when possible, but MAY be split into multiple header fields. When sending tracestate as multiple header fields, it MUST be split according to RFC7230. When receiving multiple tracestate header fields, they MUST be combined into a single header according to RFC7230.

 See the W3C specification https://www.w3.org/TR/trace-context/#tracestate-header
 for more details.
-}
module OpenTelemetry.Trace.TraceState (
  TraceState (TraceState),
  Key (..),
  Value (..),
  empty,
  insert,
  update,
  delete,
  toList,
) where

import Data.Text (Text)


newtype Key = Key Text
  deriving (Int -> Key -> ShowS
[Key] -> ShowS
Key -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Key] -> ShowS
$cshowList :: [Key] -> ShowS
show :: Key -> String
$cshow :: Key -> String
showsPrec :: Int -> Key -> ShowS
$cshowsPrec :: Int -> Key -> ShowS
Show, Key -> Key -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Key -> Key -> Bool
$c/= :: Key -> Key -> Bool
== :: Key -> Key -> Bool
$c== :: Key -> Key -> Bool
Eq, Eq Key
Key -> Key -> Bool
Key -> Key -> Ordering
Key -> Key -> Key
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 :: Key -> Key -> Key
$cmin :: Key -> Key -> Key
max :: Key -> Key -> Key
$cmax :: Key -> Key -> Key
>= :: Key -> Key -> Bool
$c>= :: Key -> Key -> Bool
> :: Key -> Key -> Bool
$c> :: Key -> Key -> Bool
<= :: Key -> Key -> Bool
$c<= :: Key -> Key -> Bool
< :: Key -> Key -> Bool
$c< :: Key -> Key -> Bool
compare :: Key -> Key -> Ordering
$ccompare :: Key -> Key -> Ordering
Ord)


newtype Value = Value Text
  deriving (Int -> Value -> ShowS
[Value] -> ShowS
Value -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Value] -> ShowS
$cshowList :: [Value] -> ShowS
show :: Value -> String
$cshow :: Value -> String
showsPrec :: Int -> Value -> ShowS
$cshowsPrec :: Int -> Value -> ShowS
Show, Value -> Value -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Value -> Value -> Bool
$c/= :: Value -> Value -> Bool
== :: Value -> Value -> Bool
$c== :: Value -> Value -> Bool
Eq, Eq Value
Value -> Value -> Bool
Value -> Value -> Ordering
Value -> Value -> Value
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 :: Value -> Value -> Value
$cmin :: Value -> Value -> Value
max :: Value -> Value -> Value
$cmax :: Value -> Value -> Value
>= :: Value -> Value -> Bool
$c>= :: Value -> Value -> Bool
> :: Value -> Value -> Bool
$c> :: Value -> Value -> Bool
<= :: Value -> Value -> Bool
$c<= :: Value -> Value -> Bool
< :: Value -> Value -> Bool
$c< :: Value -> Value -> Bool
compare :: Value -> Value -> Ordering
$ccompare :: Value -> Value -> Ordering
Ord)


{- | Data structure compliant with the storage and serialization needs of
 the W3C @tracestate@ header.
-}
newtype TraceState = TraceState [(Key, Value)]
  deriving (Int -> TraceState -> ShowS
[TraceState] -> ShowS
TraceState -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TraceState] -> ShowS
$cshowList :: [TraceState] -> ShowS
show :: TraceState -> String
$cshow :: TraceState -> String
showsPrec :: Int -> TraceState -> ShowS
$cshowsPrec :: Int -> TraceState -> ShowS
Show, TraceState -> TraceState -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TraceState -> TraceState -> Bool
$c/= :: TraceState -> TraceState -> Bool
== :: TraceState -> TraceState -> Bool
$c== :: TraceState -> TraceState -> Bool
Eq, Eq TraceState
TraceState -> TraceState -> Bool
TraceState -> TraceState -> Ordering
TraceState -> TraceState -> TraceState
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 :: TraceState -> TraceState -> TraceState
$cmin :: TraceState -> TraceState -> TraceState
max :: TraceState -> TraceState -> TraceState
$cmax :: TraceState -> TraceState -> TraceState
>= :: TraceState -> TraceState -> Bool
$c>= :: TraceState -> TraceState -> Bool
> :: TraceState -> TraceState -> Bool
$c> :: TraceState -> TraceState -> Bool
<= :: TraceState -> TraceState -> Bool
$c<= :: TraceState -> TraceState -> Bool
< :: TraceState -> TraceState -> Bool
$c< :: TraceState -> TraceState -> Bool
compare :: TraceState -> TraceState -> Ordering
$ccompare :: TraceState -> TraceState -> Ordering
Ord)


-- | An empty 'TraceState' key-value pair dictionary
empty :: TraceState
empty :: TraceState
empty = [(Key, Value)] -> TraceState
TraceState []


{- | Add a key-value pair to a 'TraceState'

 O(n)
-}
insert :: Key -> Value -> TraceState -> TraceState
insert :: Key -> Value -> TraceState -> TraceState
insert Key
k Value
v TraceState
ts = case Key -> TraceState -> TraceState
delete Key
k TraceState
ts of
  (TraceState [(Key, Value)]
l) -> [(Key, Value)] -> TraceState
TraceState ((Key
k, Value
v) forall a. a -> [a] -> [a]
: [(Key, Value)]
l)


{- | Update a value in the 'TraceState'. Does nothing if
 the value associated with the given key doesn't exist.

 O(n)
-}
update :: Key -> (Value -> Value) -> TraceState -> TraceState
update :: Key -> (Value -> Value) -> TraceState -> TraceState
update Key
k Value -> Value
f (TraceState [(Key, Value)]
ts) = case forall a. (a -> Bool) -> [a] -> ([a], [a])
break (\(Key
k', Value
_v) -> Key
k forall a. Eq a => a -> a -> Bool
== Key
k') [(Key, Value)]
ts of
  ([(Key, Value)]
before, []) -> [(Key, Value)] -> TraceState
TraceState [(Key, Value)]
before
  ([(Key, Value)]
before, (Key
_, Value
v) : [(Key, Value)]
kvs) -> [(Key, Value)] -> TraceState
TraceState ((Key
k, Value -> Value
f Value
v) forall a. a -> [a] -> [a]
: ([(Key, Value)]
before forall a. [a] -> [a] -> [a]
++ [(Key, Value)]
kvs))


{- | Remove a key-value pair for the given key.

 O(n)
-}
delete :: Key -> TraceState -> TraceState
delete :: Key -> TraceState -> TraceState
delete Key
k (TraceState [(Key, Value)]
ts) = [(Key, Value)] -> TraceState
TraceState forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter (\(Key
k', Value
_) -> Key
k' forall a. Eq a => a -> a -> Bool
/= Key
k) [(Key, Value)]
ts


{- | Convert the 'TraceState' to a list.

 O(1)
-}
toList :: TraceState -> [(Key, Value)]
toList :: TraceState -> [(Key, Value)]
toList (TraceState [(Key, Value)]
ts) = [(Key, Value)]
ts