{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  OpenTelemetry.Resource.OperatingSystem
-- Copyright   :  (c) Ian Duncan, 2021
-- License     :  BSD-3
-- Description :  Information about the operating system (OS) on which the process represented by this resource is running.
-- Maintainer  :  Ian Duncan
-- Stability   :  experimental
-- Portability :  non-portable (GHC extensions)
--
-- In case of virtualized environments, this is the operating system as it is observed by the process, i.e., the virtualized guest rather than the underlying host.
--
-----------------------------------------------------------------------------
module OpenTelemetry.Resource.OperatingSystem where
import Data.Text (Text)
import OpenTelemetry.Resource

-- | The operating system (OS) on which the process represented by this resource is running.
data OperatingSystem = OperatingSystem
  { OperatingSystem -> Text
osType :: Text
  -- ^ The operating system type.
  --
  -- MUST be one of the following or, if none of the listed values apply, a custom value:
  --
  -- +-----------------+---------------------------------------+
  -- | Value           | Description                           |
  -- +=================+=======================================+
  -- | @windows@       | Microsoft Windows                     |
  -- +-----------------+---------------------------------------+
  -- | @linux@         | Linux                                 |
  -- +-----------------+---------------------------------------+
  -- | @darwin@        | Apple Darwin                          |
  -- +-----------------+---------------------------------------+
  -- | @freebsd@       | FreeBSD                               |
  -- +-----------------+---------------------------------------+
  -- | @netbsd@        | NetBSD                                |
  -- +-----------------+---------------------------------------+
  -- | @openbsd@       | OpenBSD                               |
  -- +-----------------+---------------------------------------+
  -- | @dragonflybsd@  | DragonFly BSD                         |
  -- +-----------------+---------------------------------------+
  -- | @hpux@          | HP-UX (Hewlett Packard Unix)          |
  -- +-----------------+---------------------------------------+
  -- | @aix@           | AIX (Advanced Interactive eXecutive)  |
  -- +-----------------+---------------------------------------+
  -- | @solaris@       | Oracle Solaris                        |
  -- +-----------------+---------------------------------------+
  -- | @z_os@          | IBM z/OS                              |
  -- +-----------------+---------------------------------------+

  , OperatingSystem -> Maybe Text
osDescription :: Maybe Text
  -- ^ Human readable (not intended to be parsed) OS version information, like e.g. reported by @ver@ or @lsb_release -a@ commands.
  , OperatingSystem -> Maybe Text
osName :: Maybe Text
  -- ^ Human readable operating system name.
  , OperatingSystem -> Maybe Text
osVersion :: Maybe Text
  -- ^ The version string of the operating system as defined in
  }

instance ToResource OperatingSystem where
  type ResourceSchema OperatingSystem = 'Nothing
  -- TODO ^ schema
  toResource :: OperatingSystem -> Resource (ResourceSchema OperatingSystem)
toResource OperatingSystem{Maybe Text
Text
osVersion :: Maybe Text
osName :: Maybe Text
osDescription :: Maybe Text
osType :: Text
osVersion :: OperatingSystem -> Maybe Text
osName :: OperatingSystem -> Maybe Text
osDescription :: OperatingSystem -> Maybe Text
osType :: OperatingSystem -> Text
..} = [Maybe (Text, Attribute)] -> Resource 'Nothing
forall (r :: Maybe Symbol). [Maybe (Text, Attribute)] -> Resource r
mkResource
    [ Text
"os.type" Text -> Text -> Maybe (Text, Attribute)
forall a. ToAttribute a => Text -> a -> Maybe (Text, Attribute)
.= Text
osType
    , Text
"os.description" Text -> Maybe Text -> Maybe (Text, Attribute)
forall a.
ToAttribute a =>
Text -> Maybe a -> Maybe (Text, Attribute)
.=? Maybe Text
osDescription
    , Text
"os.name" Text -> Maybe Text -> Maybe (Text, Attribute)
forall a.
ToAttribute a =>
Text -> Maybe a -> Maybe (Text, Attribute)
.=? Maybe Text
osName
    , Text
"os.version" Text -> Maybe Text -> Maybe (Text, Attribute)
forall a.
ToAttribute a =>
Text -> Maybe a -> Maybe (Text, Attribute)
.=? Maybe Text
osVersion
    ]