module OpenTelemetry.Resource.Service.Detector where

import qualified Data.Text as T
import OpenTelemetry.Resource.Service
import System.Environment (getProgName, lookupEnv)


{- | Detect a service name using the 'OTEL_SERVICE_NAME' environment
 variable. Otherwise, populates the name with 'unknown_service:process_name'.
-}
detectService :: IO Service
detectService :: IO Service
detectService = do
  Maybe String
mSvcName <- String -> IO (Maybe String)
lookupEnv String
"OTEL_SERVICE_NAME"
  Text
svcName <- case Maybe String
mSvcName of
    Maybe String
Nothing -> String -> Text
T.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
"unknown_service:" forall a. Semigroup a => a -> a -> a
<>) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO String
getProgName
    Just String
svcName -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
svcName
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$
    Service
      { serviceName :: Text
serviceName = Text
svcName
      , serviceNamespace :: Maybe Text
serviceNamespace = forall a. Maybe a
Nothing
      , serviceInstanceId :: Maybe Text
serviceInstanceId = forall a. Maybe a
Nothing
      , serviceVersion :: Maybe Text
serviceVersion = forall a. Maybe a
Nothing
      }