{-# LANGUAGE CPP #-}

{- |
  Query basic properties of the current platform.

  All of these values are compile-time constants. If the special
  magic in the package configure step was unable to determine the
  correct value for something, it comes back as 'Nothing'.
-}

module System.Platform
    (
      -- * Operating system
      OS_Type (..), os_type,

      -- * Compiler
      compiler_name, compiler_version,

      -- * Local values
      -- $local
    )
  where

#include "Platform.h"

#ifndef HS_PNAME
#define HS_PNAME Nothing
#endif

#ifndef HS_CNAME
#define HS_CNAME Nothing
#endif

#ifndef HS_CVERS
#define HS_CVERS Nothing
#endif

-- | A list of all possible operating system types.
data OS_Type =
    -- | Some version of Microsoft Windows.
    MS_Windows |
    -- | Any sufficiently \"Unix-like\" system.
    Unix
  deriving (Eq, Show)

{- |
  The type of operating system under which we are running (or
  'Nothing' if this could not be detected).
-}
os_type :: Maybe OS_Type
os_type = HS_PNAME

{- |
  The name of the compiler (e.g., @\"GHC\"@), or 'Nothing' if
  this could not be detected.
-}
compiler_name :: Maybe String
compiler_name = HS_CNAME

{- |
  The numerical version string for the compiler
  (e.g., @\"6.10.2\"@), or 'Nothing' if this could not be detected.
-}
compiler_version :: Maybe String
compiler_version = HS_CVERS

{- $local
  Your local copy of this package was configured with the following
  settings:

  > os_type          = HS_PNAME
  > compiler_name    = HS_CNAME
  > compiler_version = HS_CVERS
-}