{-# LANGUAGE OverloadedStrings #-}
module OpenTelemetry.SemanticsConfig (
SemanticsOptions (httpOption),
HttpOption (..),
getSemanticsOptions,
getSemanticsOptions',
) where
import Control.Exception.Safe (throwIO, tryAny)
import Data.IORef (newIORef, readIORef, writeIORef)
import qualified Data.Text as T
import System.Environment (lookupEnv)
import System.IO.Unsafe (unsafePerformIO)
data SemanticsOptions = SemanticsOptions {SemanticsOptions -> HttpOption
httpOption :: HttpOption}
data HttpOption
= Stable
| StableAndOld
| Old
deriving (Int -> HttpOption -> ShowS
[HttpOption] -> ShowS
HttpOption -> String
(Int -> HttpOption -> ShowS)
-> (HttpOption -> String)
-> ([HttpOption] -> ShowS)
-> Show HttpOption
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HttpOption -> ShowS
showsPrec :: Int -> HttpOption -> ShowS
$cshow :: HttpOption -> String
show :: HttpOption -> String
$cshowList :: [HttpOption] -> ShowS
showList :: [HttpOption] -> ShowS
Show, HttpOption -> HttpOption -> Bool
(HttpOption -> HttpOption -> Bool)
-> (HttpOption -> HttpOption -> Bool) -> Eq HttpOption
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HttpOption -> HttpOption -> Bool
== :: HttpOption -> HttpOption -> Bool
$c/= :: HttpOption -> HttpOption -> Bool
/= :: HttpOption -> HttpOption -> Bool
Eq)
defaultOptions :: SemanticsOptions
defaultOptions :: SemanticsOptions
defaultOptions = SemanticsOptions {httpOption :: HttpOption
httpOption = HttpOption
Old}
parseHttpOption :: (Foldable t) => t T.Text -> HttpOption
parseHttpOption :: forall (t :: * -> *). Foldable t => t Text -> HttpOption
parseHttpOption t Text
envs
| Text
"http/dup" Text -> t Text -> Bool
forall a. Eq a => a -> t a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` t Text
envs = HttpOption
StableAndOld
| Text
"http" Text -> t Text -> Bool
forall a. Eq a => a -> t a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` t Text
envs = HttpOption
Stable
| Bool
otherwise = SemanticsOptions -> HttpOption
httpOption SemanticsOptions
defaultOptions
parseSemanticsOptions :: Maybe String -> SemanticsOptions
parseSemanticsOptions :: Maybe String -> SemanticsOptions
parseSemanticsOptions Maybe String
Nothing = SemanticsOptions
defaultOptions
parseSemanticsOptions (Just String
env) = SemanticsOptions {HttpOption
httpOption :: HttpOption
httpOption :: HttpOption
..}
where
envs :: [Text]
envs = (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Text
T.strip ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ HasCallStack => Text -> Text -> [Text]
Text -> Text -> [Text]
T.splitOn Text
"," (Text -> [Text]) -> Text -> [Text]
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
env
httpOption :: HttpOption
httpOption = [Text] -> HttpOption
forall (t :: * -> *). Foldable t => t Text -> HttpOption
parseHttpOption [Text]
envs
getSemanticsOptions' :: IO SemanticsOptions
getSemanticsOptions' :: IO SemanticsOptions
getSemanticsOptions' = Maybe String -> SemanticsOptions
parseSemanticsOptions (Maybe String -> SemanticsOptions)
-> IO (Maybe String) -> IO SemanticsOptions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO (Maybe String)
lookupEnv String
"OTEL_SEMCONV_STABILITY_OPT_IN"
memoize :: IO a -> IO (IO a)
memoize :: forall a. IO a -> IO (IO a)
memoize IO a
action = do
IORef (Maybe (Either SomeException a))
ref <- Maybe (Either SomeException a)
-> IO (IORef (Maybe (Either SomeException a)))
forall a. a -> IO (IORef a)
newIORef Maybe (Either SomeException a)
forall a. Maybe a
Nothing
IO a -> IO (IO a)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IO a -> IO (IO a)) -> IO a -> IO (IO a)
forall a b. (a -> b) -> a -> b
$ do
Maybe (Either SomeException a)
mres <- IORef (Maybe (Either SomeException a))
-> IO (Maybe (Either SomeException a))
forall a. IORef a -> IO a
readIORef IORef (Maybe (Either SomeException a))
ref
Either SomeException a
res <- case Maybe (Either SomeException a)
mres of
Just Either SomeException a
res -> Either SomeException a -> IO (Either SomeException a)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Either SomeException a
res
Maybe (Either SomeException a)
Nothing -> do
Either SomeException a
res <- IO a -> IO (Either SomeException a)
forall (m :: * -> *) a.
(HasCallStack, MonadCatch m) =>
m a -> m (Either SomeException a)
tryAny IO a
action
IORef (Maybe (Either SomeException a))
-> Maybe (Either SomeException a) -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Maybe (Either SomeException a))
ref (Maybe (Either SomeException a) -> IO ())
-> Maybe (Either SomeException a) -> IO ()
forall a b. (a -> b) -> a -> b
$ Either SomeException a -> Maybe (Either SomeException a)
forall a. a -> Maybe a
Just Either SomeException a
res
Either SomeException a -> IO (Either SomeException a)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Either SomeException a
res
(SomeException -> IO a)
-> (a -> IO a) -> Either SomeException a -> IO a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either SomeException -> IO a
forall (m :: * -> *) e a.
(HasCallStack, MonadThrow m, Exception e) =>
e -> m a
throwIO a -> IO a
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Either SomeException a
res
getSemanticsOptions :: IO SemanticsOptions
getSemanticsOptions :: IO SemanticsOptions
getSemanticsOptions = IO (IO SemanticsOptions) -> IO SemanticsOptions
forall a. IO a -> a
unsafePerformIO (IO (IO SemanticsOptions) -> IO SemanticsOptions)
-> IO (IO SemanticsOptions) -> IO SemanticsOptions
forall a b. (a -> b) -> a -> b
$ IO SemanticsOptions -> IO (IO SemanticsOptions)
forall a. IO a -> IO (IO a)
memoize IO SemanticsOptions
getSemanticsOptions'
{-# NOINLINE getSemanticsOptions #-}