{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DataKinds #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  OpenTelemetry.Resource.Container
-- Copyright   :  (c) Ian Duncan, 2021
-- License     :  BSD-3
-- Description :  Detect & provide resource info about a container
-- Maintainer  :  Ian Duncan
-- Stability   :  experimental
-- Portability :  non-portable (GHC extensions)
--
-----------------------------------------------------------------------------
module OpenTelemetry.Resource.Container where
import Data.Text (Text)
import OpenTelemetry.Resource

-- | A container instance.
data Container = Container
  { Container -> Maybe Text
containerName :: Maybe Text
  -- ^ Container name used by container runtime.
  --
  -- Examples: 'opentelemetry-autoconf'
  , Container -> Maybe Text
containerId :: Maybe Text
  -- ^ Container ID. Usually a UUID, as for example used to identify Docker containers. The UUID might be abbreviated.
  , Container -> Maybe Text
containerRuntime :: Maybe Text
  -- ^ The container runtime managing this container.
  , Container -> Maybe Text
containerImageName :: Maybe Text
  -- ^ Name of the image the container was built on.
  , Container -> Maybe Text
containerImageTag :: Maybe Text
  -- ^ Container image tag.
  }

instance ToResource Container where
  type ResourceSchema Container = 'Nothing
  toResource :: Container -> Resource (ResourceSchema Container)
toResource Container{Maybe Text
containerImageTag :: Maybe Text
containerImageName :: Maybe Text
containerRuntime :: Maybe Text
containerId :: Maybe Text
containerName :: Maybe Text
containerImageTag :: Container -> Maybe Text
containerImageName :: Container -> Maybe Text
containerRuntime :: Container -> Maybe Text
containerId :: Container -> Maybe Text
containerName :: Container -> Maybe Text
..} = [Maybe (Text, Attribute)] -> Resource 'Nothing
forall (r :: Maybe Symbol). [Maybe (Text, Attribute)] -> Resource r
mkResource 
    [ Text
"container.name" Text -> Maybe Text -> Maybe (Text, Attribute)
forall a.
ToAttribute a =>
Text -> Maybe a -> Maybe (Text, Attribute)
.=? Maybe Text
containerName
    , Text
"container.id" Text -> Maybe Text -> Maybe (Text, Attribute)
forall a.
ToAttribute a =>
Text -> Maybe a -> Maybe (Text, Attribute)
.=? Maybe Text
containerId
    , Text
"container.runtime" Text -> Maybe Text -> Maybe (Text, Attribute)
forall a.
ToAttribute a =>
Text -> Maybe a -> Maybe (Text, Attribute)
.=? Maybe Text
containerRuntime
    , Text
"container.image.name" Text -> Maybe Text -> Maybe (Text, Attribute)
forall a.
ToAttribute a =>
Text -> Maybe a -> Maybe (Text, Attribute)
.=? Maybe Text
containerImageName
    , Text
"container.image.tag" Text -> Maybe Text -> Maybe (Text, Attribute)
forall a.
ToAttribute a =>
Text -> Maybe a -> Maybe (Text, Attribute)
.=? Maybe Text
containerImageTag
    ]