{-# LANGUAGE CPP #-}

-- | Run-time settings
module GHC.Settings
  ( Settings (..)
  , ToolSettings (..)
  , FileSettings (..)
  , GhcNameVersion (..)
  , Platform (..)
  , PlatformMisc (..)
  -- * Accessors
  , dynLibSuffix
  , sProgramName
  , sProjectVersion
  , sGhcUsagePath
  , sGhciUsagePath
  , sToolDir
  , sTopDir
  , sTmpDir
  , sGlobalPackageDatabasePath
  , sLdSupportsCompactUnwind
  , sLdSupportsBuildId
  , sLdSupportsFilelist
  , sLdIsGnuLd
  , sGccSupportsNoPie
  , sPgm_L
  , sPgm_P
  , sPgm_F
  , sPgm_c
  , sPgm_a
  , sPgm_l
  , sPgm_lm
  , sPgm_dll
  , sPgm_T
  , sPgm_windres
  , sPgm_libtool
  , sPgm_ar
  , sPgm_otool
  , sPgm_install_name_tool
  , sPgm_ranlib
  , sPgm_lo
  , sPgm_lc
  , sPgm_lcc
  , sPgm_i
  , sOpt_L
  , sOpt_P
  , sOpt_P_fingerprint
  , sOpt_F
  , sOpt_c
  , sOpt_cxx
  , sOpt_a
  , sOpt_l
  , sOpt_lm
  , sOpt_windres
  , sOpt_lo
  , sOpt_lc
  , sOpt_lcc
  , sOpt_i
  , sExtraGccViaCFlags
  , sTargetPlatformString
  , sGhcWithInterpreter
  , sGhcWithSMP
  , sGhcRTSWays
  , sLibFFI
  , sGhcRtsWithLibdw
  ) where

import GHC.Prelude

import GHC.Utils.CliOption
import GHC.Utils.Fingerprint
import GHC.Platform

data Settings = Settings
  { Settings -> GhcNameVersion
sGhcNameVersion    :: {-# UNPACk #-} !GhcNameVersion
  , Settings -> FileSettings
sFileSettings      :: {-# UNPACK #-} !FileSettings
  , Settings -> Platform
sTargetPlatform    :: Platform       -- Filled in by SysTools
  , Settings -> ToolSettings
sToolSettings      :: {-# UNPACK #-} !ToolSettings
  , Settings -> PlatformMisc
sPlatformMisc      :: {-# UNPACK #-} !PlatformMisc

  -- You shouldn't need to look things up in rawSettings directly.
  -- They should have their own fields instead.
  , Settings -> [(String, String)]
sRawSettings       :: [(String, String)]
  }

-- | Settings for other executables GHC calls.
--
-- Probably should further split down by phase, or split between
-- platform-specific and platform-agnostic.
data ToolSettings = ToolSettings
  { ToolSettings -> Bool
toolSettings_ldSupportsCompactUnwind :: Bool
  , ToolSettings -> Bool
toolSettings_ldSupportsBuildId       :: Bool
  , ToolSettings -> Bool
toolSettings_ldSupportsFilelist      :: Bool
  , ToolSettings -> Bool
toolSettings_ldIsGnuLd               :: Bool
  , ToolSettings -> Bool
toolSettings_ccSupportsNoPie         :: Bool

  -- commands for particular phases
  , ToolSettings -> String
toolSettings_pgm_L       :: String
  , ToolSettings -> (String, [Option])
toolSettings_pgm_P       :: (String, [Option])
  , ToolSettings -> String
toolSettings_pgm_F       :: String
  , ToolSettings -> String
toolSettings_pgm_c       :: String
  , ToolSettings -> (String, [Option])
toolSettings_pgm_a       :: (String, [Option])
  , ToolSettings -> (String, [Option])
toolSettings_pgm_l       :: (String, [Option])
  , ToolSettings -> (String, [Option])
toolSettings_pgm_lm      :: (String, [Option])
  , ToolSettings -> (String, [Option])
toolSettings_pgm_dll     :: (String, [Option])
  , ToolSettings -> String
toolSettings_pgm_T       :: String
  , ToolSettings -> String
toolSettings_pgm_windres :: String
  , ToolSettings -> String
toolSettings_pgm_libtool :: String
  , ToolSettings -> String
toolSettings_pgm_ar      :: String
  , ToolSettings -> String
toolSettings_pgm_otool   :: String
  , ToolSettings -> String
toolSettings_pgm_install_name_tool :: String
  , ToolSettings -> String
toolSettings_pgm_ranlib  :: String
  , -- | LLVM: opt llvm optimiser
    ToolSettings -> (String, [Option])
toolSettings_pgm_lo      :: (String, [Option])
  , -- | LLVM: llc static compiler
    ToolSettings -> (String, [Option])
toolSettings_pgm_lc      :: (String, [Option])
  , -- | LLVM: c compiler
    ToolSettings -> (String, [Option])
toolSettings_pgm_lcc     :: (String, [Option])
  , ToolSettings -> String
toolSettings_pgm_i       :: String

  -- options for particular phases
  , ToolSettings -> [String]
toolSettings_opt_L             :: [String]
  , ToolSettings -> [String]
toolSettings_opt_P             :: [String]
  , -- | cached Fingerprint of sOpt_P
    -- See Note [Repeated -optP hashing]
    ToolSettings -> Fingerprint
toolSettings_opt_P_fingerprint :: Fingerprint
  , ToolSettings -> [String]
toolSettings_opt_F             :: [String]
  , ToolSettings -> [String]
toolSettings_opt_c             :: [String]
  , ToolSettings -> [String]
toolSettings_opt_cxx           :: [String]
  , ToolSettings -> [String]
toolSettings_opt_a             :: [String]
  , ToolSettings -> [String]
toolSettings_opt_l             :: [String]
  , ToolSettings -> [String]
toolSettings_opt_lm            :: [String]
  , ToolSettings -> [String]
toolSettings_opt_windres       :: [String]
  , -- | LLVM: llvm optimiser
    ToolSettings -> [String]
toolSettings_opt_lo            :: [String]
  , -- | LLVM: llc static compiler
    ToolSettings -> [String]
toolSettings_opt_lc            :: [String]
  , -- | LLVM: c compiler
    ToolSettings -> [String]
toolSettings_opt_lcc           :: [String]
  , -- | iserv options
    ToolSettings -> [String]
toolSettings_opt_i             :: [String]

  , ToolSettings -> [String]
toolSettings_extraGccViaCFlags :: [String]
  }


-- | Paths to various files and directories used by GHC, including those that
-- provide more settings.
data FileSettings = FileSettings
  { FileSettings -> String
fileSettings_ghcUsagePath          :: FilePath       -- ditto
  , FileSettings -> String
fileSettings_ghciUsagePath         :: FilePath       -- ditto
  , FileSettings -> Maybe String
fileSettings_toolDir               :: Maybe FilePath -- ditto
  , FileSettings -> String
fileSettings_topDir                :: FilePath       -- ditto
  , FileSettings -> String
fileSettings_tmpDir                :: String      -- no trailing '/'
  , FileSettings -> String
fileSettings_globalPackageDatabase :: FilePath
  }


-- | Settings for what GHC this is.
data GhcNameVersion = GhcNameVersion
  { GhcNameVersion -> String
ghcNameVersion_programName    :: String
  , GhcNameVersion -> String
ghcNameVersion_projectVersion :: String
  }

-- | Dynamic library suffix
dynLibSuffix :: GhcNameVersion -> String
dynLibSuffix :: GhcNameVersion -> String
dynLibSuffix (GhcNameVersion String
name String
ver) = Char
'-'forall a. a -> [a] -> [a]
:String
name forall a. [a] -> [a] -> [a]
++ String
ver

-----------------------------------------------------------------------------
-- Accessessors from 'Settings'

sProgramName         :: Settings -> String
sProgramName :: Settings -> String
sProgramName = GhcNameVersion -> String
ghcNameVersion_programName forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> GhcNameVersion
sGhcNameVersion
sProjectVersion      :: Settings -> String
sProjectVersion :: Settings -> String
sProjectVersion = GhcNameVersion -> String
ghcNameVersion_projectVersion forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> GhcNameVersion
sGhcNameVersion

sGhcUsagePath        :: Settings -> FilePath
sGhcUsagePath :: Settings -> String
sGhcUsagePath = FileSettings -> String
fileSettings_ghcUsagePath forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> FileSettings
sFileSettings
sGhciUsagePath       :: Settings -> FilePath
sGhciUsagePath :: Settings -> String
sGhciUsagePath = FileSettings -> String
fileSettings_ghciUsagePath forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> FileSettings
sFileSettings
sToolDir             :: Settings -> Maybe FilePath
sToolDir :: Settings -> Maybe String
sToolDir = FileSettings -> Maybe String
fileSettings_toolDir forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> FileSettings
sFileSettings
sTopDir              :: Settings -> FilePath
sTopDir :: Settings -> String
sTopDir = FileSettings -> String
fileSettings_topDir forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> FileSettings
sFileSettings
sTmpDir              :: Settings -> String
sTmpDir :: Settings -> String
sTmpDir = FileSettings -> String
fileSettings_tmpDir forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> FileSettings
sFileSettings
sGlobalPackageDatabasePath :: Settings -> FilePath
sGlobalPackageDatabasePath :: Settings -> String
sGlobalPackageDatabasePath = FileSettings -> String
fileSettings_globalPackageDatabase forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> FileSettings
sFileSettings

sLdSupportsCompactUnwind :: Settings -> Bool
sLdSupportsCompactUnwind :: Settings -> Bool
sLdSupportsCompactUnwind = ToolSettings -> Bool
toolSettings_ldSupportsCompactUnwind forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sLdSupportsBuildId :: Settings -> Bool
sLdSupportsBuildId :: Settings -> Bool
sLdSupportsBuildId = ToolSettings -> Bool
toolSettings_ldSupportsBuildId forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sLdSupportsFilelist :: Settings -> Bool
sLdSupportsFilelist :: Settings -> Bool
sLdSupportsFilelist = ToolSettings -> Bool
toolSettings_ldSupportsFilelist forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sLdIsGnuLd :: Settings -> Bool
sLdIsGnuLd :: Settings -> Bool
sLdIsGnuLd = ToolSettings -> Bool
toolSettings_ldIsGnuLd forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sGccSupportsNoPie :: Settings -> Bool
sGccSupportsNoPie :: Settings -> Bool
sGccSupportsNoPie = ToolSettings -> Bool
toolSettings_ccSupportsNoPie forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings

sPgm_L :: Settings -> String
sPgm_L :: Settings -> String
sPgm_L = ToolSettings -> String
toolSettings_pgm_L forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_P :: Settings -> (String, [Option])
sPgm_P :: Settings -> (String, [Option])
sPgm_P = ToolSettings -> (String, [Option])
toolSettings_pgm_P forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_F :: Settings -> String
sPgm_F :: Settings -> String
sPgm_F = ToolSettings -> String
toolSettings_pgm_F forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_c :: Settings -> String
sPgm_c :: Settings -> String
sPgm_c = ToolSettings -> String
toolSettings_pgm_c forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_a :: Settings -> (String, [Option])
sPgm_a :: Settings -> (String, [Option])
sPgm_a = ToolSettings -> (String, [Option])
toolSettings_pgm_a forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_l :: Settings -> (String, [Option])
sPgm_l :: Settings -> (String, [Option])
sPgm_l = ToolSettings -> (String, [Option])
toolSettings_pgm_l forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_lm :: Settings -> (String, [Option])
sPgm_lm :: Settings -> (String, [Option])
sPgm_lm = ToolSettings -> (String, [Option])
toolSettings_pgm_lm forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_dll :: Settings -> (String, [Option])
sPgm_dll :: Settings -> (String, [Option])
sPgm_dll = ToolSettings -> (String, [Option])
toolSettings_pgm_dll forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_T :: Settings -> String
sPgm_T :: Settings -> String
sPgm_T = ToolSettings -> String
toolSettings_pgm_T forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_windres :: Settings -> String
sPgm_windres :: Settings -> String
sPgm_windres = ToolSettings -> String
toolSettings_pgm_windres forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_libtool :: Settings -> String
sPgm_libtool :: Settings -> String
sPgm_libtool = ToolSettings -> String
toolSettings_pgm_libtool forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_ar :: Settings -> String
sPgm_ar :: Settings -> String
sPgm_ar = ToolSettings -> String
toolSettings_pgm_ar forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_otool :: Settings -> String
sPgm_otool :: Settings -> String
sPgm_otool = ToolSettings -> String
toolSettings_pgm_otool forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_install_name_tool :: Settings -> String
sPgm_install_name_tool :: Settings -> String
sPgm_install_name_tool = ToolSettings -> String
toolSettings_pgm_install_name_tool forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_ranlib :: Settings -> String
sPgm_ranlib :: Settings -> String
sPgm_ranlib = ToolSettings -> String
toolSettings_pgm_ranlib forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_lo :: Settings -> (String, [Option])
sPgm_lo :: Settings -> (String, [Option])
sPgm_lo = ToolSettings -> (String, [Option])
toolSettings_pgm_lo forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_lc :: Settings -> (String, [Option])
sPgm_lc :: Settings -> (String, [Option])
sPgm_lc = ToolSettings -> (String, [Option])
toolSettings_pgm_lc forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_lcc :: Settings -> (String, [Option])
sPgm_lcc :: Settings -> (String, [Option])
sPgm_lcc = ToolSettings -> (String, [Option])
toolSettings_pgm_lcc forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_i :: Settings -> String
sPgm_i :: Settings -> String
sPgm_i = ToolSettings -> String
toolSettings_pgm_i forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_L :: Settings -> [String]
sOpt_L :: Settings -> [String]
sOpt_L = ToolSettings -> [String]
toolSettings_opt_L forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_P :: Settings -> [String]
sOpt_P :: Settings -> [String]
sOpt_P = ToolSettings -> [String]
toolSettings_opt_P forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_P_fingerprint :: Settings -> Fingerprint
sOpt_P_fingerprint :: Settings -> Fingerprint
sOpt_P_fingerprint = ToolSettings -> Fingerprint
toolSettings_opt_P_fingerprint forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_F :: Settings -> [String]
sOpt_F :: Settings -> [String]
sOpt_F = ToolSettings -> [String]
toolSettings_opt_F forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_c :: Settings -> [String]
sOpt_c :: Settings -> [String]
sOpt_c = ToolSettings -> [String]
toolSettings_opt_c forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_cxx :: Settings -> [String]
sOpt_cxx :: Settings -> [String]
sOpt_cxx = ToolSettings -> [String]
toolSettings_opt_cxx forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_a :: Settings -> [String]
sOpt_a :: Settings -> [String]
sOpt_a = ToolSettings -> [String]
toolSettings_opt_a forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_l :: Settings -> [String]
sOpt_l :: Settings -> [String]
sOpt_l = ToolSettings -> [String]
toolSettings_opt_l forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_lm :: Settings -> [String]
sOpt_lm :: Settings -> [String]
sOpt_lm = ToolSettings -> [String]
toolSettings_opt_lm forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_windres :: Settings -> [String]
sOpt_windres :: Settings -> [String]
sOpt_windres = ToolSettings -> [String]
toolSettings_opt_windres forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_lo :: Settings -> [String]
sOpt_lo :: Settings -> [String]
sOpt_lo = ToolSettings -> [String]
toolSettings_opt_lo forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_lc :: Settings -> [String]
sOpt_lc :: Settings -> [String]
sOpt_lc = ToolSettings -> [String]
toolSettings_opt_lc forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_lcc :: Settings -> [String]
sOpt_lcc :: Settings -> [String]
sOpt_lcc = ToolSettings -> [String]
toolSettings_opt_lcc forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_i :: Settings -> [String]
sOpt_i :: Settings -> [String]
sOpt_i = ToolSettings -> [String]
toolSettings_opt_i forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings

sExtraGccViaCFlags :: Settings -> [String]
sExtraGccViaCFlags :: Settings -> [String]
sExtraGccViaCFlags = ToolSettings -> [String]
toolSettings_extraGccViaCFlags forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings

sTargetPlatformString :: Settings -> String
sTargetPlatformString :: Settings -> String
sTargetPlatformString = PlatformMisc -> String
platformMisc_targetPlatformString forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> PlatformMisc
sPlatformMisc
sGhcWithInterpreter :: Settings -> Bool
sGhcWithInterpreter :: Settings -> Bool
sGhcWithInterpreter = PlatformMisc -> Bool
platformMisc_ghcWithInterpreter forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> PlatformMisc
sPlatformMisc
sGhcWithSMP :: Settings -> Bool
sGhcWithSMP :: Settings -> Bool
sGhcWithSMP = PlatformMisc -> Bool
platformMisc_ghcWithSMP forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> PlatformMisc
sPlatformMisc
sGhcRTSWays :: Settings -> String
sGhcRTSWays :: Settings -> String
sGhcRTSWays = PlatformMisc -> String
platformMisc_ghcRTSWays forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> PlatformMisc
sPlatformMisc
sLibFFI :: Settings -> Bool
sLibFFI :: Settings -> Bool
sLibFFI = PlatformMisc -> Bool
platformMisc_libFFI forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> PlatformMisc
sPlatformMisc
sGhcRtsWithLibdw :: Settings -> Bool
sGhcRtsWithLibdw :: Settings -> Bool
sGhcRtsWithLibdw = PlatformMisc -> Bool
platformMisc_ghcRtsWithLibdw forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> PlatformMisc
sPlatformMisc