{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module OpenTelemetry.Resource (
mkResource,
Resource,
(.=),
(.=?),
ResourceMerge,
mergeResources,
ToResource (..),
MaterializeResource,
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 = Attributes -> Resource r
forall (schema :: Maybe Symbol). Attributes -> Resource schema
Resource (Attributes -> Resource r)
-> ([Maybe (Text, Attribute)] -> Attributes)
-> [Maybe (Text, Attribute)]
-> Resource r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Text, Attribute)] -> Attributes
unsafeAttributesFromListIgnoringLimits ([(Text, Attribute)] -> Attributes)
-> ([Maybe (Text, Attribute)] -> [(Text, Attribute)])
-> [Maybe (Text, Attribute)]
-> Attributes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe (Text, Attribute)] -> [(Text, Attribute)]
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 = (Text, Attribute) -> Maybe (Text, Attribute)
forall a. a -> Maybe a
Just (Text
k, a -> Attribute
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', a -> Attribute
forall a. ToAttribute a => a -> Attribute
toAttribute a
v)) Text
k (a -> (Text, Attribute)) -> Maybe a -> Maybe (Text, Attribute)
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) = Attributes -> Resource s
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 = Attributes -> Resource s
forall (schema :: Maybe Symbol). Attributes -> Resource schema
Resource Attributes
emptyAttributes
type family ResourceMerge (schemaLeft :: Maybe Symbol) (schemaRight :: Maybe Symbol) :: Maybe Symbol where
ResourceMerge 'Nothing a = a
ResourceMerge a 'Nothing = a
ResourceMerge ('Just s) ('Just s) = 'Just s
mergeResources
:: Resource new
-> Resource old
-> Resource (ResourceMerge new old)
mergeResources :: forall (new :: Maybe Symbol) (old :: Maybe Symbol).
Resource new -> Resource old -> Resource (ResourceMerge new old)
mergeResources (Resource Attributes
l) (Resource Attributes
r) = Attributes -> Resource (ResourceMerge new old)
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 Maybe String
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 (String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> String -> Maybe String
forall a b. (a -> b) -> a -> b
$ Proxy s -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (forall {k} (t :: k). Proxy t
forall (t :: Symbol). Proxy t
Proxy @s)) Attributes
attrs
data MaterializedResources = MaterializedResources
{ MaterializedResources -> Maybe String
materializedResourcesSchema :: Maybe String
, MaterializedResources -> Attributes
materializedResourcesAttributes :: Attributes
}
deriving (Int -> MaterializedResources -> ShowS
[MaterializedResources] -> ShowS
MaterializedResources -> String
(Int -> MaterializedResources -> ShowS)
-> (MaterializedResources -> String)
-> ([MaterializedResources] -> ShowS)
-> Show MaterializedResources
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MaterializedResources -> ShowS
showsPrec :: Int -> MaterializedResources -> ShowS
$cshow :: MaterializedResources -> String
show :: MaterializedResources -> String
$cshowList :: [MaterializedResources] -> ShowS
showList :: [MaterializedResources] -> ShowS
Show, MaterializedResources -> MaterializedResources -> Bool
(MaterializedResources -> MaterializedResources -> Bool)
-> (MaterializedResources -> MaterializedResources -> Bool)
-> Eq MaterializedResources
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MaterializedResources -> MaterializedResources -> Bool
== :: MaterializedResources -> MaterializedResources -> Bool
$c/= :: MaterializedResources -> MaterializedResources -> Bool
/= :: MaterializedResources -> MaterializedResources -> Bool
Eq)
emptyMaterializedResources :: MaterializedResources
emptyMaterializedResources :: MaterializedResources
emptyMaterializedResources = Maybe String -> Attributes -> MaterializedResources
MaterializedResources Maybe String
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