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
(Int -> Key -> ShowS)
-> (Key -> String) -> ([Key] -> ShowS) -> Show Key
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Key -> ShowS
showsPrec :: Int -> Key -> ShowS
$cshow :: Key -> String
show :: Key -> String
$cshowList :: [Key] -> ShowS
showList :: [Key] -> ShowS
Show, Key -> Key -> Bool
(Key -> Key -> Bool) -> (Key -> Key -> Bool) -> Eq Key
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Key -> Key -> Bool
== :: Key -> Key -> Bool
$c/= :: Key -> Key -> Bool
/= :: Key -> Key -> Bool
Eq, Eq Key
Eq Key =>
(Key -> Key -> Ordering)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Key)
-> (Key -> Key -> Key)
-> Ord 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
$ccompare :: Key -> Key -> Ordering
compare :: Key -> Key -> Ordering
$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
>= :: Key -> Key -> Bool
$cmax :: Key -> Key -> Key
max :: Key -> Key -> Key
$cmin :: Key -> Key -> Key
min :: Key -> Key -> Key
Ord)
newtype Value = Value Text
deriving (Int -> Value -> ShowS
[Value] -> ShowS
Value -> String
(Int -> Value -> ShowS)
-> (Value -> String) -> ([Value] -> ShowS) -> Show Value
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Value -> ShowS
showsPrec :: Int -> Value -> ShowS
$cshow :: Value -> String
show :: Value -> String
$cshowList :: [Value] -> ShowS
showList :: [Value] -> ShowS
Show, Value -> Value -> Bool
(Value -> Value -> Bool) -> (Value -> Value -> Bool) -> Eq Value
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Value -> Value -> Bool
== :: Value -> Value -> Bool
$c/= :: Value -> Value -> Bool
/= :: Value -> Value -> Bool
Eq, Eq Value
Eq Value =>
(Value -> Value -> Ordering)
-> (Value -> Value -> Bool)
-> (Value -> Value -> Bool)
-> (Value -> Value -> Bool)
-> (Value -> Value -> Bool)
-> (Value -> Value -> Value)
-> (Value -> Value -> Value)
-> Ord 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
$ccompare :: Value -> Value -> Ordering
compare :: Value -> Value -> Ordering
$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
>= :: Value -> Value -> Bool
$cmax :: Value -> Value -> Value
max :: Value -> Value -> Value
$cmin :: Value -> Value -> Value
min :: Value -> Value -> Value
Ord)
newtype TraceState = TraceState [(Key, Value)]
deriving (Int -> TraceState -> ShowS
[TraceState] -> ShowS
TraceState -> String
(Int -> TraceState -> ShowS)
-> (TraceState -> String)
-> ([TraceState] -> ShowS)
-> Show TraceState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TraceState -> ShowS
showsPrec :: Int -> TraceState -> ShowS
$cshow :: TraceState -> String
show :: TraceState -> String
$cshowList :: [TraceState] -> ShowS
showList :: [TraceState] -> ShowS
Show, TraceState -> TraceState -> Bool
(TraceState -> TraceState -> Bool)
-> (TraceState -> TraceState -> Bool) -> Eq TraceState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TraceState -> TraceState -> Bool
== :: TraceState -> TraceState -> Bool
$c/= :: TraceState -> TraceState -> Bool
/= :: TraceState -> TraceState -> Bool
Eq, Eq TraceState
Eq TraceState =>
(TraceState -> TraceState -> Ordering)
-> (TraceState -> TraceState -> Bool)
-> (TraceState -> TraceState -> Bool)
-> (TraceState -> TraceState -> Bool)
-> (TraceState -> TraceState -> Bool)
-> (TraceState -> TraceState -> TraceState)
-> (TraceState -> TraceState -> TraceState)
-> Ord 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
$ccompare :: TraceState -> TraceState -> Ordering
compare :: TraceState -> TraceState -> Ordering
$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
>= :: TraceState -> TraceState -> Bool
$cmax :: TraceState -> TraceState -> TraceState
max :: TraceState -> TraceState -> TraceState
$cmin :: TraceState -> TraceState -> TraceState
min :: TraceState -> TraceState -> TraceState
Ord)
empty :: TraceState
empty :: TraceState
empty = [(Key, Value)] -> TraceState
TraceState []
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) (Key, Value) -> [(Key, Value)] -> [(Key, Value)]
forall a. a -> [a] -> [a]
: [(Key, Value)]
l)
update :: Key -> (Value -> Value) -> TraceState -> TraceState
update :: Key -> (Value -> Value) -> TraceState -> TraceState
update Key
k Value -> Value
f (TraceState [(Key, Value)]
ts) = case ((Key, Value) -> Bool)
-> [(Key, Value)] -> ([(Key, Value)], [(Key, Value)])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (\(Key
k', Value
_v) -> Key
k Key -> Key -> Bool
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) (Key, Value) -> [(Key, Value)] -> [(Key, Value)]
forall a. a -> [a] -> [a]
: ([(Key, Value)]
before [(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. [a] -> [a] -> [a]
++ [(Key, Value)]
kvs))
delete :: Key -> TraceState -> TraceState
delete :: Key -> TraceState -> TraceState
delete Key
k (TraceState [(Key, Value)]
ts) = [(Key, Value)] -> TraceState
TraceState ([(Key, Value)] -> TraceState) -> [(Key, Value)] -> TraceState
forall a b. (a -> b) -> a -> b
$ ((Key, Value) -> Bool) -> [(Key, Value)] -> [(Key, Value)]
forall a. (a -> Bool) -> [a] -> [a]
filter (\(Key
k', Value
_) -> Key
k' Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
/= Key
k) [(Key, Value)]
ts
toList :: TraceState -> [(Key, Value)]
toList :: TraceState -> [(Key, Value)]
toList (TraceState [(Key, Value)]
ts) = [(Key, Value)]
ts