{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  OpenTelemetry.Trace.Id
-- Copyright   :  (c) Ian Duncan, 2021
-- License     :  BSD-3
-- Description :  Trace and Span ID generation, validation, serialization, and deserialization
-- Maintainer  :  Ian Duncan
-- Stability   :  experimental
-- Portability :  non-portable (GHC extensions)
--
-- Trace and Span Id generation
--
-- No Aeson instances are provided since they've got the potential to be
-- transport-specific in format. Use newtypes for serialisation instead.
--
-----------------------------------------------------------------------------
module OpenTelemetry.Trace.Id 
  ( -- * Working with 'TraceId's
    TraceId
    -- ** Creating 'TraceId's
  , newTraceId
    -- ** Checking 'TraceId's for validity
  , isEmptyTraceId
    -- ** Encoding / decoding 'TraceId' from bytes
  , traceIdBytes
  , bytesToTraceId
    -- ** Encoding / decoding 'TraceId' from a given 'Base' encoding
  , baseEncodedToTraceId
  , traceIdBaseEncodedBuilder
  , traceIdBaseEncodedByteString
  , traceIdBaseEncodedText
    -- * Working with 'SpanId's
  , SpanId
    -- ** Creating 'SpanId's
  , newSpanId
    -- ** Checking 'SpanId's for validity
  , isEmptySpanId
    -- ** Encoding / decoding 'SpanId' from bytes
  , spanIdBytes
  , bytesToSpanId
    -- ** Encoding / decoding 'SpanId' from a given 'Base' encoding
  , 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)

-- TODO faster encoding decoding via something like
-- https://github.com/lemire/Code-used-on-Daniel-Lemire-s-blog/blob/03fc2e82fdef2c6fd25721203e1654428fee123d/2019/04/17/hexparse.cpp#L390

-- | A valid trace identifier is a 16-byte array with at least one non-zero byte.
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)

-- | A valid span identifier is an 8-byte array with at least one non-zero byte.
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


-- | bytes pointed to by src to the hexadecimal binary representation.
toHexadecimal :: ShortByteString -- ^ source bytes
              -> ShortByteString -- ^ hexadecimal output
toHexadecimal :: ShortByteString -> ShortByteString
toHexadecimal (SBS ByteArray#
bin) = (forall s. ST s ShortByteString) -> ShortByteString
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s ShortByteString) -> ShortByteString)
-> (forall s. ST s ShortByteString) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ STRep s ShortByteString -> ST s ShortByteString
forall s a. STRep s a -> ST s a
ST (STRep s ShortByteString -> ST s ShortByteString)
-> STRep s ShortByteString -> ST s ShortByteString
forall a b. (a -> b) -> a -> b
$ \State# s
s ->
  case Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
newByteArray# (Int#
n Int# -> Int# -> Int#
*# Int#
2# ) State# s
s of
    (# State# s
s1, MutableByteArray# s
mba #) -> case Int# -> MutableByteArray# s -> State# s -> State# s
forall d. Int# -> MutableByteArray# d -> State# d -> State# d
loop Int#
0# MutableByteArray# s
mba State# s
s1 of
      State# s
s2 -> case MutableByteArray# s -> State# s -> (# State# s, ByteArray# #)
forall d.
MutableByteArray# d -> State# d -> (# State# d, ByteArray# #)
unsafeFreezeByteArray# MutableByteArray# s
mba State# s
s2 of
        (# State# s
s3, ByteArray#
ba #) -> (# State# s
s3, ByteArray# -> ShortByteString
SBS ByteArray#
ba #)
  where
    !n :: Int#
n = ByteArray# -> Int#
sizeofByteArray# ByteArray#
bin
    loop :: Int# -> MutableByteArray# d -> State# d -> State# d
loop Int#
i MutableByteArray# d
bout State# d
s
      | Int# -> Bool
isTrue# (Int#
i Int# -> Int# -> Int#
==# Int#
n) = State# d
s
      | Bool
otherwise = do
          let !w :: Word#
w = ByteArray# -> Int# -> Word#
indexWord8Array# ByteArray#
bin Int#
i
          let !(# Word#
w1, Word#
w2 #) = Word# -> (# Word#, Word# #)
convertByte Word#
w
          case MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
forall d.
MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
writeWord8Array# MutableByteArray# d
bout (Int#
i Int# -> Int# -> Int#
*# Int#
2#) Word#
w1 State# d
s of
            State# d
s1 -> case MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
forall d.
MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
writeWord8Array# MutableByteArray# d
bout ((Int#
i Int# -> Int# -> Int#
*# Int#
2#) Int# -> Int# -> Int#
+# Int#
1#) Word#
w2 State# d
s1 of
              State# d
s2 -> Int# -> MutableByteArray# d -> State# d -> State# d
loop (Int#
i Int# -> Int# -> Int#
+# Int#
1#) MutableByteArray# d
bout State# d
s2

-- | Convert a value Word# to two Word#s containing
-- the hexadecimal representation of the Word#
convertByte :: Word# -> (# Word#, Word# #)
convertByte :: Word# -> (# Word#, Word# #)
convertByte Word#
b = (# Addr# -> Word# -> Word#
r Addr#
tableHi Word#
b, Addr# -> Word# -> Word#
r Addr#
tableLo Word#
b #)
  where
        r :: Addr# -> Word# -> Word#
        r :: Addr# -> Word# -> Word#
r Addr#
table Word#
ix = Addr# -> Int# -> Word#
indexWord8OffAddr# Addr#
table (Word# -> Int#
word2Int# Word#
ix)

        !tableLo :: Addr#
tableLo =
            Addr#
"0123456789abcdef0123456789abcdef\
            \0123456789abcdef0123456789abcdef\
            \0123456789abcdef0123456789abcdef\
            \0123456789abcdef0123456789abcdef\
            \0123456789abcdef0123456789abcdef\
            \0123456789abcdef0123456789abcdef\
            \0123456789abcdef0123456789abcdef\
            \0123456789abcdef0123456789abcdef"#
        !tableHi :: Addr#
tableHi =
            Addr#
"00000000000000001111111111111111\
            \22222222222222223333333333333333\
            \44444444444444445555555555555555\
            \66666666666666667777777777777777\
            \88888888888888889999999999999999\
            \aaaaaaaaaaaaaaaabbbbbbbbbbbbbbbb\
            \ccccccccccccccccdddddddddddddddd\
            \eeeeeeeeeeeeeeeeffffffffffffffff"#
{-# INLINE convertByte #-}

-- | Convert a base16 @src to the byte equivalent.
--
-- length of the 'ShortByteString' input must be even
--
-- TODO, not working right
fromHexadecimal :: ShortByteString -> (Maybe ShortByteString)
fromHexadecimal :: ShortByteString -> Maybe ShortByteString
fromHexadecimal src :: ShortByteString
src@(SBS ByteArray#
sbs)
  | Int -> Bool
forall a. Integral a => a -> Bool
odd (ShortByteString -> Int
length ShortByteString
src) = Maybe ShortByteString
forall a. Maybe a
Nothing
  | Bool
otherwise = (forall s. ST s (Maybe ShortByteString)) -> Maybe ShortByteString
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s (Maybe ShortByteString)) -> Maybe ShortByteString)
-> (forall s. ST s (Maybe ShortByteString))
-> Maybe ShortByteString
forall a b. (a -> b) -> a -> b
$ STRep s (Maybe ShortByteString) -> ST s (Maybe ShortByteString)
forall s a. STRep s a -> ST s a
ST (STRep s (Maybe ShortByteString) -> ST s (Maybe ShortByteString))
-> STRep s (Maybe ShortByteString) -> ST s (Maybe ShortByteString)
forall a b. (a -> b) -> a -> b
$ \State# s
s -> case Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
newByteArray# Int#
newLen# State# s
s of
      (# State# s
s1, MutableByteArray# s
dst #) -> case MutableByteArray# s
-> Int# -> Int# -> State# s -> (# State# s, Maybe Int #)
forall d.
MutableByteArray# d
-> Int# -> Int# -> State# d -> (# State# d, Maybe Int #)
loop MutableByteArray# s
dst Int#
0# Int#
0# State# s
s1 of
        (# State# s
s2, Just Int
_ #) -> (# State# s
s2, Maybe ShortByteString
forall a. Maybe a
Nothing #)
        (# State# s
s2, Maybe Int
Nothing #) -> case MutableByteArray# s -> State# s -> (# State# s, ByteArray# #)
forall d.
MutableByteArray# d -> State# d -> (# State# d, ByteArray# #)
unsafeFreezeByteArray# MutableByteArray# s
dst State# s
s2 of
          (# State# s
s3, ByteArray#
sbs' #) -> (# State# s
s3, ShortByteString -> Maybe ShortByteString
forall a. a -> Maybe a
Just (ShortByteString -> Maybe ShortByteString)
-> ShortByteString -> Maybe ShortByteString
forall a b. (a -> b) -> a -> b
$ ByteArray# -> ShortByteString
SBS ByteArray#
sbs' #)
  where
    !(I# Int#
newLen#) = ShortByteString -> Int
length ShortByteString
src Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2
    loop :: MutableByteArray# d
-> Int# -> Int# -> State# d -> (# State# d, Maybe Int #)
loop MutableByteArray# d
dst Int#
di Int#
i State# d
s
      | Int# -> Bool
isTrue# (Int#
i Int# -> Int# -> Int#
==# Int#
newLen#) = (# State# d
s, Maybe Int
forall a. Maybe a
Nothing #)
      | Bool
otherwise = do
        let a :: Word#
a = Word# -> Word#
rHi (ByteArray# -> Int# -> Word#
indexWord8Array# ByteArray#
sbs Int#
i)
        let b :: Word#
b = Word# -> Word#
rLo (ByteArray# -> Int# -> Word#
indexWord8Array# ByteArray#
sbs (Int#
i Int# -> Int# -> Int#
+# Int#
1#))
        if Int# -> Bool
isTrue# (Word# -> Word# -> Int#
eqWord# Word#
a (Int# -> Word#
int2Word# Int#
0xff#)) Bool -> Bool -> Bool
|| Int# -> Bool
isTrue# (Word# -> Word# -> Int#
eqWord# Word#
b (Int# -> Word#
int2Word# Int#
0xff#))
            then (# State# d
s, Int -> Maybe Int
forall a. a -> Maybe a
Just (Int# -> Int
I# Int#
i) #)
            else
              case MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
forall d.
MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
writeWord8Array# MutableByteArray# d
dst Int#
di (Word# -> Word# -> Word#
or# Word#
a Word#
b) State# d
s of
                State# d
s1 -> MutableByteArray# d
-> Int# -> Int# -> State# d -> (# State# d, Maybe Int #)
loop MutableByteArray# d
dst (Int#
di Int# -> Int# -> Int#
+# Int#
1#) (Int#
i Int# -> Int# -> Int#
+# Int#
2#) State# d
s1

    rLo :: Word# -> Word#
rLo Word#
ix = Addr# -> Int# -> Word#
indexWord8OffAddr# Addr#
tableLo (Word# -> Int#
word2Int# Word#
ix)
    rHi :: Word# -> Word#
rHi Word#
ix = Addr# -> Int# -> Word#
indexWord8OffAddr# Addr#
tableHi (Word# -> Int#
word2Int# Word#
ix)

    !tableLo :: Addr#
tableLo =
            Addr#
"\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\x00\x01\x02\x03\x04\x05\x06\x07\x08\x09\xff\xff\xff\xff\xff\xff\
              \\xff\x0a\x0b\x0c\x0d\x0e\x0f\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\x0a\x0b\x0c\x0d\x0e\x0f\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff"#
    !tableHi :: Addr#
tableHi =
            Addr#
"\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\x00\x10\x20\x30\x40\x50\x60\x70\x80\x90\xff\xff\xff\xff\xff\xff\
              \\xff\xa0\xb0\xc0\xd0\xe0\xf0\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xa0\xb0\xc0\xd0\xe0\xf0\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
              \\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff"#

-- | Generate a 'TraceId' using the provided 'IdGenerator'
--
-- This function is generally called by the @hs-opentelemetry-sdk@,
-- but may be useful in some testing situations.
--
-- @since 0.1.0.0
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)

-- | Check whether all bytes in the 'TraceId' are zero.
--
-- @since 0.1.0.0
isEmptyTraceId :: TraceId -> Bool
isEmptyTraceId :: TraceId -> Bool
isEmptyTraceId (TraceId (SBS ByteArray#
arr)) =
  Int# -> Bool
isTrue#
    (Word# -> Word# -> Int#
eqWord#
      (Word# -> Word# -> Word#
or#
        (ByteArray# -> Int# -> Word#
indexWord64Array# ByteArray#
arr Int#
0#)
        (ByteArray# -> Int# -> Word#
indexWord64Array# ByteArray#
arr Int#
1#))
      (Int# -> Word#
int2Word# Int#
0#))

-- | Access the byte-level representation of the provided 'TraceId'
--
-- @since 0.1.0.0
traceIdBytes :: TraceId -> ByteString
traceIdBytes :: TraceId -> ByteString
traceIdBytes (TraceId ShortByteString
bytes) = ShortByteString -> ByteString
fromShort ShortByteString
bytes

-- | Convert a 'ByteString' to a 'TraceId'. Will fail if the 'ByteString'
-- is not exactly 16 bytes long.
--
-- @since 0.1.0.0
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"

-- | Convert a 'ByteString' of a specified base-encoding into a 'TraceId'.
-- Will fail if the decoded value is not exactly 16 bytes long.
--
-- @since 0.1.0.0
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

-- | Output a 'TraceId' into a base-encoded bytestring 'Builder'.
--
-- @since 0.1.0.0
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

-- | Output a 'TraceId' into a base-encoded 'ByteString'.
--
-- @since 0.1.0.0
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

-- | Output a 'TraceId' into a base-encoded 'Text'.
--
-- @since 0.1.0.0
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

-- | Generate a 'SpanId' using the provided 'IdGenerator'
--
-- This function is generally called by the @hs-opentelemetry-sdk@,
-- but may be useful in some testing situations.
--
-- @since 0.1.0.0
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)

-- | Check whether all bytes in the 'SpanId' are zero.
--
-- @since 0.1.0.0
isEmptySpanId :: SpanId -> Bool
isEmptySpanId :: SpanId -> Bool
isEmptySpanId (SpanId (SBS ByteArray#
arr)) = Int# -> Bool
isTrue#
  (Word# -> Word# -> Int#
eqWord#
    (ByteArray# -> Int# -> Word#
indexWord64Array# ByteArray#
arr Int#
0#)
    (Int# -> Word#
int2Word# Int#
0#))

-- | Access the byte-level representation of the provided 'SpanId'
--
-- @since 0.1.0.0
spanIdBytes :: SpanId -> ByteString
spanIdBytes :: SpanId -> ByteString
spanIdBytes (SpanId ShortByteString
bytes) = ShortByteString -> ByteString
fromShort ShortByteString
bytes

-- | Convert a 'ByteString' of a specified base-encoding into a 'SpanId'.
-- Will fail if the decoded value is not exactly 8 bytes long.
--
-- @since 0.1.0.0
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"

-- | Convert a 'ByteString' of a specified base-encoding into a 'SpanId'.
-- Will fail if the decoded value is not exactly 8 bytes long.
--
-- @since 0.1.0.0
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

-- | Output a 'SpanId' into a base-encoded bytestring 'Builder'.
--
-- @since 0.1.0.0
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

-- | Output a 'SpanId' into a base-encoded 'ByteString'.
--
-- @since 0.1.0.0
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

-- | Output a 'SpanId' into a base-encoded 'Text'.
--
-- @since 0.1.0.0
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