{-# LANGUAGE CPP  #-}
{-# LANGUAGE Safe #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  System.Info
-- Copyright   :  (c) The University of Glasgow 2001
-- License     :  BSD-style (see the file libraries/base/LICENSE)
--
-- Maintainer  :  libraries@haskell.org
-- Stability   :  experimental
-- Portability :  portable
--
-- Information about the characteristics of the host
-- system lucky enough to run your program.
--
-- For a comprehensive listing of supported platforms, please refer to
-- https://gitlab.haskell.org/ghc/ghc/-/wikis/platforms
-----------------------------------------------------------------------------

module System.Info
  ( os
  , arch
  , compilerName
  , compilerVersion
  , fullCompilerVersion
  ) where

import           Data.Version (Version (..))

-- | The version of 'compilerName' with which the program was compiled
-- or is being interpreted.
--
-- ==== __Example__
-- > ghci> compilerVersion
-- > Version {versionBranch = [8,8], versionTags = []}
compilerVersion :: Version
compilerVersion :: Version
compilerVersion = [Int] -> [String] -> Version
Version [Int
major, Int
minor] []
  where (Int
major, Int
minor) = Int
compilerVersionRaw Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
`divMod` Int
100

-- | The full version of 'compilerName' with which the program was compiled
-- or is being interpreted. It includes the major, minor, revision and an additional
-- identifier, generally in the form "<year><month><day>".
fullCompilerVersion :: Version
fullCompilerVersion :: Version
fullCompilerVersion = [Int] -> [String] -> Version
Version [Int]
version []
  where
    version :: [Int]
    version :: [Int]
version = (String -> Int) -> [String] -> [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Int
forall a. Read a => String -> a
read ([String] -> [Int]) -> [String] -> [Int]
forall a b. (a -> b) -> a -> b
$ String -> [String]
splitVersion __GLASGOW_HASKELL_FULL_VERSION__

splitVersion :: String -> [String]
splitVersion :: String -> [String]
splitVersion String
s =
  case (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.') String
s of
    String
"" -> []
    String
s' -> let (String
w, String
s'') = (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.') String
s'
           in String
w String -> [String] -> [String]
forall a. a -> [a] -> [a]
: String -> [String]
splitVersion String
s''

#include "ghcplatform.h"

-- | The operating system on which the program is running.
-- Common values include:
--
--     * "darwin" — macOS
--     * "freebsd"
--     * "linux"
--     * "linux-android"
--     * "mingw32" — Windows
--     * "netbsd"
--     * "openbsd"
os :: String
os :: String
os = String
HOST_OS

-- | The machine architecture on which the program is running.
-- Common values include:
--
--    * "aarch64"
--    * "alpha"
--    * "arm"
--    * "hppa"
--    * "hppa1_1"
--    * "i386"
--    * "ia64"
--    * "m68k"
--    * "mips"
--    * "mipseb"
--    * "mipsel"
--    * "nios2"
--    * "powerpc"
--    * "powerpc64"
--    * "powerpc64le"
--    * "riscv32"
--    * "riscv64"
--    * "rs6000"
--    * "s390"
--    * "s390x"
--    * "sh4"
--    * "sparc"
--    * "sparc64"
--    * "vax"
--    * "x86_64"
arch :: String
arch :: String
arch = HOST_ARCH

-- | The Haskell implementation with which the program was compiled
-- or is being interpreted.
-- On the GHC platform, the value is "ghc".
compilerName :: String
compilerName :: String
compilerName = String
"ghc"

compilerVersionRaw :: Int
compilerVersionRaw :: Int
compilerVersionRaw = __GLASGOW_HASKELL__