{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
module OpenTelemetry.Resource (
mkResource,
Resource,
(.=),
(.=?),
ResourceMerge,
mergeResources,
ToResource (..),
materializeResources,
MaterializedResources,
emptyMaterializedResources,
getMaterializedResourcesSchema,
getMaterializedResourcesAttributes,
) where
import Data.Maybe (catMaybes)
import Data.Proxy (Proxy (..))
import Data.Text (Text)
import GHC.TypeLits
import OpenTelemetry.Attributes
newtype Resource (schema :: Maybe Symbol) = Resource Attributes
mkResource :: [Maybe (Text, Attribute)] -> Resource r
mkResource :: forall (r :: Maybe Symbol). [Maybe (Text, Attribute)] -> Resource r
mkResource = forall (schema :: Maybe Symbol). Attributes -> Resource schema
Resource forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Text, Attribute)] -> Attributes
unsafeAttributesFromListIgnoringLimits forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [Maybe a] -> [a]
catMaybes
(.=) :: ToAttribute a => Text -> a -> Maybe (Text, Attribute)
Text
k .= :: forall a. ToAttribute a => Text -> a -> Maybe (Text, Attribute)
.= a
v = forall a. a -> Maybe a
Just (Text
k, forall a. ToAttribute a => a -> Attribute
toAttribute a
v)
(.=?) :: ToAttribute a => Text -> Maybe a -> Maybe (Text, Attribute)
Text
k .=? :: forall a.
ToAttribute a =>
Text -> Maybe a -> Maybe (Text, Attribute)
.=? Maybe a
mv = (\Text
k' a
v -> (Text
k', forall a. ToAttribute a => a -> Attribute
toAttribute a
v)) Text
k forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe a
mv
instance Semigroup (Resource s) where
<> :: Resource s -> Resource s -> Resource s
(<>) (Resource Attributes
l) (Resource Attributes
r) = forall (schema :: Maybe Symbol). Attributes -> Resource schema
Resource (Attributes -> Attributes -> Attributes
unsafeMergeAttributesIgnoringLimits Attributes
l Attributes
r)
instance Monoid (Resource s) where
mempty :: Resource s
mempty = forall (schema :: Maybe Symbol). Attributes -> Resource schema
Resource Attributes
emptyAttributes
type family ResourceMerge schemaLeft schemaRight :: Maybe Symbol where
ResourceMerge 'Nothing 'Nothing = 'Nothing
ResourceMerge 'Nothing ('Just s) = 'Just s
ResourceMerge ('Just s) 'Nothing = 'Just s
ResourceMerge ('Just s) ('Just s) = 'Just s
mergeResources ::
Resource old ->
Resource new ->
Resource (ResourceMerge old new)
mergeResources :: forall (old :: Maybe Symbol) (new :: Maybe Symbol).
Resource old -> Resource new -> Resource (ResourceMerge old new)
mergeResources (Resource Attributes
l) (Resource Attributes
r) = forall (schema :: Maybe Symbol). Attributes -> Resource schema
Resource (Attributes -> Attributes -> Attributes
unsafeMergeAttributesIgnoringLimits Attributes
l Attributes
r)
class ToResource a where
type ResourceSchema a :: Maybe Symbol
type ResourceSchema a = 'Nothing
toResource :: a -> Resource (ResourceSchema a)
class MaterializeResource schema where
materializeResources :: Resource schema -> MaterializedResources
instance MaterializeResource 'Nothing where
materializeResources :: Resource 'Nothing -> MaterializedResources
materializeResources (Resource Attributes
attrs) = Maybe String -> Attributes -> MaterializedResources
MaterializedResources forall a. Maybe a
Nothing Attributes
attrs
instance KnownSymbol s => MaterializeResource ('Just s) where
materializeResources :: Resource ('Just s) -> MaterializedResources
materializeResources (Resource Attributes
attrs) = Maybe String -> Attributes -> MaterializedResources
MaterializedResources (forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (forall {k} (t :: k). Proxy t
Proxy @s)) Attributes
attrs
data MaterializedResources = MaterializedResources
{ MaterializedResources -> Maybe String
materializedResourcesSchema :: Maybe String
, MaterializedResources -> Attributes
materializedResourcesAttributes :: Attributes
}
emptyMaterializedResources :: MaterializedResources
emptyMaterializedResources :: MaterializedResources
emptyMaterializedResources = Maybe String -> Attributes -> MaterializedResources
MaterializedResources forall a. Maybe a
Nothing Attributes
emptyAttributes
getMaterializedResourcesSchema :: MaterializedResources -> Maybe String
getMaterializedResourcesSchema :: MaterializedResources -> Maybe String
getMaterializedResourcesSchema = MaterializedResources -> Maybe String
materializedResourcesSchema
getMaterializedResourcesAttributes :: MaterializedResources -> Attributes
getMaterializedResourcesAttributes :: MaterializedResources -> Attributes
getMaterializedResourcesAttributes = MaterializedResources -> Attributes
materializedResourcesAttributes