{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
module OpenTelemetry.Trace.Id
(
TraceId
, newTraceId
, isEmptyTraceId
, traceIdBytes
, bytesToTraceId
, baseEncodedToTraceId
, traceIdBaseEncodedBuilder
, traceIdBaseEncodedByteString
, traceIdBaseEncodedText
, SpanId
, newSpanId
, isEmptySpanId
, spanIdBytes
, bytesToSpanId
, Base(..)
, baseEncodedToSpanId
, spanIdBaseEncodedBuilder
, spanIdBaseEncodedByteString
, spanIdBaseEncodedText
) where
import OpenTelemetry.Trace.Id.Generator
import Control.Monad.IO.Class
import Data.ByteArray.Encoding
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import Data.ByteString.Builder (Builder)
import qualified Data.ByteString.Builder as B
import Data.Hashable (Hashable)
import Data.Text (Text)
import Data.Text.Encoding (decodeUtf8)
import Data.ByteString.Short.Internal
import GHC.Exts
import GHC.ST
import Prelude hiding (length)
newtype TraceId = TraceId ShortByteString
deriving stock (Eq TraceId
Eq TraceId
-> (TraceId -> TraceId -> Ordering)
-> (TraceId -> TraceId -> Bool)
-> (TraceId -> TraceId -> Bool)
-> (TraceId -> TraceId -> Bool)
-> (TraceId -> TraceId -> Bool)
-> (TraceId -> TraceId -> TraceId)
-> (TraceId -> TraceId -> TraceId)
-> Ord TraceId
TraceId -> TraceId -> Bool
TraceId -> TraceId -> Ordering
TraceId -> TraceId -> TraceId
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 :: TraceId -> TraceId -> TraceId
$cmin :: TraceId -> TraceId -> TraceId
max :: TraceId -> TraceId -> TraceId
$cmax :: TraceId -> TraceId -> TraceId
>= :: TraceId -> TraceId -> Bool
$c>= :: TraceId -> TraceId -> Bool
> :: TraceId -> TraceId -> Bool
$c> :: TraceId -> TraceId -> Bool
<= :: TraceId -> TraceId -> Bool
$c<= :: TraceId -> TraceId -> Bool
< :: TraceId -> TraceId -> Bool
$c< :: TraceId -> TraceId -> Bool
compare :: TraceId -> TraceId -> Ordering
$ccompare :: TraceId -> TraceId -> Ordering
$cp1Ord :: Eq TraceId
Ord, TraceId -> TraceId -> Bool
(TraceId -> TraceId -> Bool)
-> (TraceId -> TraceId -> Bool) -> Eq TraceId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TraceId -> TraceId -> Bool
$c/= :: TraceId -> TraceId -> Bool
== :: TraceId -> TraceId -> Bool
$c== :: TraceId -> TraceId -> Bool
Eq)
deriving newtype (Eq TraceId
Eq TraceId
-> (Int -> TraceId -> Int) -> (TraceId -> Int) -> Hashable TraceId
Int -> TraceId -> Int
TraceId -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: TraceId -> Int
$chash :: TraceId -> Int
hashWithSalt :: Int -> TraceId -> Int
$chashWithSalt :: Int -> TraceId -> Int
$cp1Hashable :: Eq TraceId
Hashable)
newtype SpanId = SpanId ShortByteString
deriving stock (Eq SpanId
Eq SpanId
-> (SpanId -> SpanId -> Ordering)
-> (SpanId -> SpanId -> Bool)
-> (SpanId -> SpanId -> Bool)
-> (SpanId -> SpanId -> Bool)
-> (SpanId -> SpanId -> Bool)
-> (SpanId -> SpanId -> SpanId)
-> (SpanId -> SpanId -> SpanId)
-> Ord SpanId
SpanId -> SpanId -> Bool
SpanId -> SpanId -> Ordering
SpanId -> SpanId -> SpanId
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 :: SpanId -> SpanId -> SpanId
$cmin :: SpanId -> SpanId -> SpanId
max :: SpanId -> SpanId -> SpanId
$cmax :: SpanId -> SpanId -> SpanId
>= :: SpanId -> SpanId -> Bool
$c>= :: SpanId -> SpanId -> Bool
> :: SpanId -> SpanId -> Bool
$c> :: SpanId -> SpanId -> Bool
<= :: SpanId -> SpanId -> Bool
$c<= :: SpanId -> SpanId -> Bool
< :: SpanId -> SpanId -> Bool
$c< :: SpanId -> SpanId -> Bool
compare :: SpanId -> SpanId -> Ordering
$ccompare :: SpanId -> SpanId -> Ordering
$cp1Ord :: Eq SpanId
Ord, SpanId -> SpanId -> Bool
(SpanId -> SpanId -> Bool)
-> (SpanId -> SpanId -> Bool) -> Eq SpanId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SpanId -> SpanId -> Bool
$c/= :: SpanId -> SpanId -> Bool
== :: SpanId -> SpanId -> Bool
$c== :: SpanId -> SpanId -> Bool
Eq)
deriving newtype (Eq SpanId
Eq SpanId
-> (Int -> SpanId -> Int) -> (SpanId -> Int) -> Hashable SpanId
Int -> SpanId -> Int
SpanId -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: SpanId -> Int
$chash :: SpanId -> Int
hashWithSalt :: Int -> SpanId -> Int
$chashWithSalt :: Int -> SpanId -> Int
$cp1Hashable :: Eq SpanId
Hashable)
instance Show TraceId where
show :: TraceId -> String
show = Text -> String
forall a. Show a => a -> String
show (Text -> String) -> (TraceId -> Text) -> TraceId -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base -> TraceId -> Text
traceIdBaseEncodedText Base
Base16
instance IsString TraceId where
fromString :: String -> TraceId
fromString String
str = case Base -> ByteString -> Either String TraceId
baseEncodedToTraceId Base
Base16 (String -> ByteString
forall a. IsString a => String -> a
fromString String
str) of
Left String
err -> String -> TraceId
forall a. HasCallStack => String -> a
error String
err
Right TraceId
ok -> TraceId
ok
instance Show SpanId where
show :: SpanId -> String
show = Text -> String
forall a. Show a => a -> String
show (Text -> String) -> (SpanId -> Text) -> SpanId -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base -> SpanId -> Text
spanIdBaseEncodedText Base
Base16
instance IsString SpanId where
fromString :: String -> SpanId
fromString String
str = case Base -> ByteString -> Either String SpanId
baseEncodedToSpanId Base
Base16 (String -> ByteString
forall a. IsString a => String -> a
fromString String
str) of
Left String
err -> String -> SpanId
forall a. HasCallStack => String -> a
error String
err
Right SpanId
ok -> SpanId
ok
newTraceId :: MonadIO m => IdGenerator -> m TraceId
newTraceId :: IdGenerator -> m TraceId
newTraceId IdGenerator
gen = IO TraceId -> m TraceId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (ShortByteString -> TraceId
TraceId (ShortByteString -> TraceId)
-> (ByteString -> ShortByteString) -> ByteString -> TraceId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ShortByteString
toShort (ByteString -> TraceId) -> IO ByteString -> IO TraceId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IdGenerator -> IO ByteString
generateTraceIdBytes IdGenerator
gen)
isEmptyTraceId :: TraceId -> Bool
isEmptyTraceId :: TraceId -> Bool
isEmptyTraceId (TraceId (SBS ByteArray#
arr)) =
Int# -> Bool
isTrue#
(Word# -> Word# -> Int#
eqWord#
(Word# -> Word# -> Word#
or#
#if MIN_VERSION_base(4,17,0)
(word64ToWord# (indexWord64Array# arr 0#))
(word64ToWord# (indexWord64Array# arr 1#)))
#else
(ByteArray# -> Int# -> Word#
indexWord64Array# ByteArray#
arr Int#
0#)
(ByteArray# -> Int# -> Word#
indexWord64Array# ByteArray#
arr Int#
1#))
#endif
(Int# -> Word#
int2Word# Int#
0#))
traceIdBytes :: TraceId -> ByteString
traceIdBytes :: TraceId -> ByteString
traceIdBytes (TraceId ShortByteString
bytes) = ShortByteString -> ByteString
fromShort ShortByteString
bytes
bytesToTraceId :: ByteString -> Either String TraceId
bytesToTraceId :: ByteString -> Either String TraceId
bytesToTraceId ByteString
bs = if ByteString -> Int
BS.length ByteString
bs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
16
then TraceId -> Either String TraceId
forall a b. b -> Either a b
Right (TraceId -> Either String TraceId)
-> TraceId -> Either String TraceId
forall a b. (a -> b) -> a -> b
$ ShortByteString -> TraceId
TraceId (ShortByteString -> TraceId) -> ShortByteString -> TraceId
forall a b. (a -> b) -> a -> b
$ ByteString -> ShortByteString
toShort ByteString
bs
else String -> Either String TraceId
forall a b. a -> Either a b
Left String
"bytesToTraceId: TraceId must be 8 bytes long"
baseEncodedToTraceId :: Base -> ByteString -> Either String TraceId
baseEncodedToTraceId :: Base -> ByteString -> Either String TraceId
baseEncodedToTraceId Base
b ByteString
bs = do
ByteString
r <- Base -> ByteString -> Either String ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
Base -> bin -> Either String bout
convertFromBase Base
b ByteString
bs
ByteString -> Either String TraceId
bytesToTraceId ByteString
r
traceIdBaseEncodedBuilder :: Base -> TraceId -> Builder
traceIdBaseEncodedBuilder :: Base -> TraceId -> Builder
traceIdBaseEncodedBuilder Base
b = ByteString -> Builder
B.byteString (ByteString -> Builder)
-> (TraceId -> ByteString) -> TraceId -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base -> ByteString -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
Base -> bin -> bout
convertToBase Base
b (ByteString -> ByteString)
-> (TraceId -> ByteString) -> TraceId -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TraceId -> ByteString
traceIdBytes
traceIdBaseEncodedByteString :: Base -> TraceId -> ByteString
traceIdBaseEncodedByteString :: Base -> TraceId -> ByteString
traceIdBaseEncodedByteString Base
b = Base -> ByteString -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
Base -> bin -> bout
convertToBase Base
b (ByteString -> ByteString)
-> (TraceId -> ByteString) -> TraceId -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TraceId -> ByteString
traceIdBytes
traceIdBaseEncodedText :: Base -> TraceId -> Text
traceIdBaseEncodedText :: Base -> TraceId -> Text
traceIdBaseEncodedText Base
b = ByteString -> Text
decodeUtf8 (ByteString -> Text) -> (TraceId -> ByteString) -> TraceId -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base -> TraceId -> ByteString
traceIdBaseEncodedByteString Base
b
newSpanId :: MonadIO m => IdGenerator -> m SpanId
newSpanId :: IdGenerator -> m SpanId
newSpanId IdGenerator
gen = IO SpanId -> m SpanId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (ShortByteString -> SpanId
SpanId (ShortByteString -> SpanId)
-> (ByteString -> ShortByteString) -> ByteString -> SpanId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ShortByteString
toShort (ByteString -> SpanId) -> IO ByteString -> IO SpanId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IdGenerator -> IO ByteString
generateSpanIdBytes IdGenerator
gen)
isEmptySpanId :: SpanId -> Bool
isEmptySpanId :: SpanId -> Bool
isEmptySpanId (SpanId (SBS ByteArray#
arr)) = Int# -> Bool
isTrue#
(Word# -> Word# -> Int#
eqWord#
#if MIN_VERSION_base(4,17,0)
(word64ToWord# (indexWord64Array# arr 0#))
#else
(ByteArray# -> Int# -> Word#
indexWord64Array# ByteArray#
arr Int#
0#)
#endif
(Int# -> Word#
int2Word# Int#
0#))
spanIdBytes :: SpanId -> ByteString
spanIdBytes :: SpanId -> ByteString
spanIdBytes (SpanId ShortByteString
bytes) = ShortByteString -> ByteString
fromShort ShortByteString
bytes
bytesToSpanId :: ByteString -> Either String SpanId
bytesToSpanId :: ByteString -> Either String SpanId
bytesToSpanId ByteString
bs = if ByteString -> Int
BS.length ByteString
bs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
8
then SpanId -> Either String SpanId
forall a b. b -> Either a b
Right (SpanId -> Either String SpanId) -> SpanId -> Either String SpanId
forall a b. (a -> b) -> a -> b
$ ShortByteString -> SpanId
SpanId (ShortByteString -> SpanId) -> ShortByteString -> SpanId
forall a b. (a -> b) -> a -> b
$ ByteString -> ShortByteString
toShort ByteString
bs
else String -> Either String SpanId
forall a b. a -> Either a b
Left String
"bytesToSpanId: SpanId must be 8 bytes long"
baseEncodedToSpanId :: Base -> ByteString -> Either String SpanId
baseEncodedToSpanId :: Base -> ByteString -> Either String SpanId
baseEncodedToSpanId Base
b ByteString
bs = do
ByteString
r <- Base -> ByteString -> Either String ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
Base -> bin -> Either String bout
convertFromBase Base
b ByteString
bs
ByteString -> Either String SpanId
bytesToSpanId ByteString
r
spanIdBaseEncodedBuilder :: Base -> SpanId -> Builder
spanIdBaseEncodedBuilder :: Base -> SpanId -> Builder
spanIdBaseEncodedBuilder Base
b = ByteString -> Builder
B.byteString (ByteString -> Builder)
-> (SpanId -> ByteString) -> SpanId -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base -> ByteString -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
Base -> bin -> bout
convertToBase Base
b (ByteString -> ByteString)
-> (SpanId -> ByteString) -> SpanId -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SpanId -> ByteString
spanIdBytes
spanIdBaseEncodedByteString :: Base -> SpanId -> ByteString
spanIdBaseEncodedByteString :: Base -> SpanId -> ByteString
spanIdBaseEncodedByteString Base
b = Base -> ByteString -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
Base -> bin -> bout
convertToBase Base
b (ByteString -> ByteString)
-> (SpanId -> ByteString) -> SpanId -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SpanId -> ByteString
spanIdBytes
spanIdBaseEncodedText :: Base -> SpanId -> Text
spanIdBaseEncodedText :: Base -> SpanId -> Text
spanIdBaseEncodedText Base
b = ByteString -> Text
decodeUtf8 (ByteString -> Text) -> (SpanId -> ByteString) -> SpanId -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base -> SpanId -> ByteString
spanIdBaseEncodedByteString Base
b