{-# LANGUAGE CPP #-}
module OpenTelemetry.Trace.Id.Generator.Default 
  ( defaultIdGenerator
  ) where

import System.Random.MWC
#if MIN_VERSION_random(1,2,0)
import System.Random.Stateful
#else
import Data.ByteString.Random
#endif
import System.IO.Unsafe (unsafePerformIO)
import OpenTelemetry.Trace.Id.Generator (IdGenerator(..))

-- | The default generator for trace and span ids.
--
-- @since 0.1.0.0
defaultIdGenerator :: IdGenerator
defaultIdGenerator :: IdGenerator
defaultIdGenerator = IO IdGenerator -> IdGenerator
forall a. IO a -> a
unsafePerformIO (IO IdGenerator -> IdGenerator) -> IO IdGenerator -> IdGenerator
forall a b. (a -> b) -> a -> b
$ do
  Gen RealWorld
g <- IO (Gen RealWorld)
IO GenIO
createSystemRandom
#if MIN_VERSION_random(1,2,0)
  IdGenerator -> IO IdGenerator
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IdGenerator -> IO IdGenerator) -> IdGenerator -> IO IdGenerator
forall a b. (a -> b) -> a -> b
$ IdGenerator :: IO ByteString -> IO ByteString -> IdGenerator
IdGenerator
    { generateSpanIdBytes :: IO ByteString
generateSpanIdBytes = Int -> Gen RealWorld -> IO ByteString
forall g (m :: * -> *). StatefulGen g m => Int -> g -> m ByteString
uniformByteStringM Int
8 Gen RealWorld
g
    , generateTraceIdBytes :: IO ByteString
generateTraceIdBytes = Int -> Gen RealWorld -> IO ByteString
forall g (m :: * -> *). StatefulGen g m => Int -> g -> m ByteString
uniformByteStringM Int
16 Gen RealWorld
g
    }
#else
  pure $ IdGenerator
    { generateSpanIdBytes = randomGen g 8
    , generateTraceIdBytes = randomGen g 16
    }
#endif
{-# NOINLINE defaultIdGenerator #-}