summaryrefslogtreecommitdiff
path: root/compiler
diff options
context:
space:
mode:
authorJohn Ericson <git@JohnEricson.me>2019-05-21 23:00:27 -0400
committerMarge Bot <ben+marge-bot@smart-cactus.org>2019-05-29 16:06:45 -0400
commitace2e3350fa7da1f7ebcdb882f1241da10a90c26 (patch)
treea6ea9a688e3bf1230e8775e9f41a86576a9523b4 /compiler
parent2d2aa2031b9abc3bff7b5585ab4201948c8bba7d (diff)
downloadhaskell-ace2e3350fa7da1f7ebcdb882f1241da10a90c26.tar.gz
Break up `Settings` into smaller structs
As far as I can tell, the fields within `Settings` aren't *intrinsicly* related. They just happen to be initialized the same way (in particular prior to the rest of `DynFlags`), and that is why they are grouped together. Within `Settings`, however, there are groups of settings that clearly do share something in common, regardless of how they anything is initialized. In the spirit of GHC being a library, where the end cosumer may choose to initialize this configuration in arbitrary ways, I made some new data types for thoses groups internal to `Settings`, and used them to define `Settings` instead. Hopefully this is a baby step towards a general decoupling of the stateful and stateless parts of GHC.
Diffstat (limited to 'compiler')
-rw-r--r--compiler/ghc.cabal.in5
-rw-r--r--compiler/main/CliOption.hs27
-rw-r--r--compiler/main/DynFlags.hs238
-rw-r--r--compiler/main/FileSettings.hs16
-rw-r--r--compiler/main/GhcNameVersion.hs11
-rw-r--r--compiler/main/Settings.hs203
-rw-r--r--compiler/main/SysTools.hs139
-rw-r--r--compiler/main/ToolSettings.hs64
-rw-r--r--compiler/utils/Platform.hs28
9 files changed, 541 insertions, 190 deletions
diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in
index 38ef67d495..e2d789b172 100644
--- a/compiler/ghc.cabal.in
+++ b/compiler/ghc.cabal.in
@@ -272,7 +272,10 @@ Library
CmmType
CmmUtils
CmmLayoutStack
+ CliOption
EnumSet
+ GhcNameVersion
+ FileSettings
MkGraph
PprBase
PprC
@@ -395,6 +398,7 @@ Library
Plugins
TcPluginM
PprTyThing
+ Settings
StaticPtrTable
SysTools
SysTools.BaseDir
@@ -418,6 +422,7 @@ Library
PrelNames
PrelRules
PrimOp
+ ToolSettings
TysPrim
TysWiredIn
CostCentre
diff --git a/compiler/main/CliOption.hs b/compiler/main/CliOption.hs
new file mode 100644
index 0000000000..d42c5b4900
--- /dev/null
+++ b/compiler/main/CliOption.hs
@@ -0,0 +1,27 @@
+module CliOption
+ ( Option (..)
+ , showOpt
+ ) where
+
+import GhcPrelude
+
+-- -----------------------------------------------------------------------------
+-- Command-line options
+
+-- | When invoking external tools as part of the compilation pipeline, we
+-- pass these a sequence of options on the command-line. Rather than
+-- just using a list of Strings, we use a type that allows us to distinguish
+-- between filepaths and 'other stuff'. The reason for this is that
+-- this type gives us a handle on transforming filenames, and filenames only,
+-- to whatever format they're expected to be on a particular platform.
+data Option
+ = FileOption -- an entry that _contains_ filename(s) / filepaths.
+ String -- a non-filepath prefix that shouldn't be
+ -- transformed (e.g., "/out=")
+ String -- the filepath/filename portion
+ | Option String
+ deriving ( Eq )
+
+showOpt :: Option -> String
+showOpt (FileOption pre f) = pre ++ f
+showOpt (Option s) = s
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 15f254ad7c..1f0fb2f7ef 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -87,7 +87,66 @@ module DynFlags (
-- ** System tool settings and locations
Settings(..),
+ sProgramName,
+ sProjectVersion,
+ sGhcUsagePath,
+ sGhciUsagePath,
+ sToolDir,
+ sTopDir,
+ sTmpDir,
+ sSystemPackageConfig,
+ sLdSupportsCompactUnwind,
+ sLdSupportsBuildId,
+ sLdSupportsFilelist,
+ sLdIsGnuLd,
+ sGccSupportsNoPie,
+ sPgm_L,
+ sPgm_P,
+ sPgm_F,
+ sPgm_c,
+ sPgm_a,
+ sPgm_l,
+ sPgm_dll,
+ sPgm_T,
+ sPgm_windres,
+ sPgm_libtool,
+ sPgm_ar,
+ 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_windres,
+ sOpt_lo,
+ sOpt_lc,
+ sOpt_lcc,
+ sOpt_i,
+ sExtraGccViaCFlags,
+ sTargetPlatformString,
+ sIntegerLibrary,
+ sIntegerLibraryType,
+ sGhcWithInterpreter,
+ sGhcWithNativeCodeGen,
+ sGhcWithSMP,
+ sGhcRTSWays,
+ sTablesNextToCode,
+ sLeadingUnderscore,
+ sLibFFI,
+ sGhcThreaded,
+ sGhcDebugged,
+ sGhcRtsWithLibdw,
IntegerLibrary(..),
+ GhcNameVersion(..),
+ FileSettings(..),
+ PlatformMisc(..),
targetPlatform, programName, projectVersion,
ghcUsagePath, ghciUsagePath, topDir, tmpDir, rawSettings,
versionedAppDir,
@@ -198,9 +257,11 @@ import {-# SOURCE #-} PrelNames ( mAIN )
import {-# SOURCE #-} Packages (PackageState, emptyPackageState)
import DriverPhases ( Phase(..), phaseInputExt )
import Config
+import CliOption
import CmdLineParser hiding (WarnReason(..))
import qualified CmdLineParser as Cmd
import Constants
+import GhcNameVersion
import Panic
import qualified PprColour as Col
import Util
@@ -211,7 +272,11 @@ import SrcLoc
import BasicTypes ( Alignment, alignmentOf, IntWithInf, treatZeroAsInf )
import FastString
import Fingerprint
+import FileSettings
import Outputable
+import Settings
+import ToolSettings
+
import Foreign.C ( CInt(..) )
import System.IO.Unsafe ( unsafeDupablePerformIO )
import {-# SOURCE #-} ErrUtils ( Severity(..), MsgDoc, mkLocMessageAnn
@@ -1304,80 +1369,8 @@ type LlvmTargets = [(String, LlvmTarget)]
type LlvmPasses = [(Int, String)]
type LlvmConfig = (LlvmTargets, LlvmPasses)
-data IntegerLibrary
- = IntegerGMP
- | IntegerSimple
- deriving (Read, Show, Eq)
-
-data Settings = Settings {
- sTargetPlatform :: Platform, -- Filled in by SysTools
- sGhcUsagePath :: FilePath, -- ditto
- sGhciUsagePath :: FilePath, -- ditto
- sToolDir :: Maybe FilePath, -- ditto
- sTopDir :: FilePath, -- ditto
- sTmpDir :: String, -- no trailing '/'
- sProgramName :: String,
- sProjectVersion :: String,
- -- You shouldn't need to look things up in rawSettings directly.
- -- They should have their own fields instead.
- sRawSettings :: [(String, String)],
- sExtraGccViaCFlags :: [String],
- sSystemPackageConfig :: FilePath,
- sLdSupportsCompactUnwind :: Bool,
- sLdSupportsBuildId :: Bool,
- sLdSupportsFilelist :: Bool,
- sLdIsGnuLd :: Bool,
- sGccSupportsNoPie :: Bool,
- -- commands for particular phases
- sPgm_L :: String,
- sPgm_P :: (String,[Option]),
- sPgm_F :: String,
- sPgm_c :: (String,[Option]),
- sPgm_a :: (String,[Option]),
- sPgm_l :: (String,[Option]),
- sPgm_dll :: (String,[Option]),
- sPgm_T :: String,
- sPgm_windres :: String,
- sPgm_libtool :: String,
- sPgm_ar :: String,
- sPgm_ranlib :: String,
- sPgm_lo :: (String,[Option]), -- LLVM: opt llvm optimiser
- sPgm_lc :: (String,[Option]), -- LLVM: llc static compiler
- sPgm_lcc :: (String,[Option]), -- LLVM: c compiler
- sPgm_i :: String,
- -- options for particular phases
- sOpt_L :: [String],
- sOpt_P :: [String],
- sOpt_P_fingerprint :: Fingerprint, -- cached Fingerprint of sOpt_P
- -- See Note [Repeated -optP hashing]
- sOpt_F :: [String],
- sOpt_c :: [String],
- sOpt_cxx :: [String],
- sOpt_a :: [String],
- sOpt_l :: [String],
- sOpt_windres :: [String],
- sOpt_lo :: [String], -- LLVM: llvm optimiser
- sOpt_lc :: [String], -- LLVM: llc static compiler
- sOpt_lcc :: [String], -- LLVM: c compiler
- sOpt_i :: [String], -- iserv options
-
- sPlatformConstants :: PlatformConstants,
-
- -- Formerly Config.hs, target specific
- sTargetPlatformString :: String, -- TODO Recalculate string from richer info?
- sIntegerLibrary :: String,
- sIntegerLibraryType :: IntegerLibrary,
- sGhcWithInterpreter :: Bool,
- sGhcWithNativeCodeGen :: Bool,
- sGhcWithSMP :: Bool,
- sGhcRTSWays :: String,
- sTablesNextToCode :: Bool,
- sLeadingUnderscore :: Bool,
- sLibFFI :: Bool,
- sGhcThreaded :: Bool,
- sGhcDebugged :: Bool,
- sGhcRtsWithLibdw :: Bool
- }
+-----------------------------------------------------------------------------
+-- Accessessors from 'DynFlags'
targetPlatform :: DynFlags -> Platform
targetPlatform dflags = sTargetPlatform (settings dflags)
@@ -2671,14 +2664,16 @@ setDumpPrefixForce f d = d { dumpPrefixForce = f}
-- XXX HACK: Prelude> words "'does not' work" ===> ["'does","not'","work"]
-- Config.hs should really use Option.
-setPgmP f = let (pgm:args) = words f in alterSettings (\s -> s { sPgm_P = (pgm, map Option args)})
-addOptl f = alterSettings (\s -> s { sOpt_l = f : sOpt_l s})
-addOptc f = alterSettings (\s -> s { sOpt_c = f : sOpt_c s})
-addOptcxx f = alterSettings (\s -> s { sOpt_cxx = f : sOpt_cxx s})
-addOptP f = alterSettings (\s -> s { sOpt_P = f : sOpt_P s
- , sOpt_P_fingerprint = fingerprintStrings (f : sOpt_P s)
- })
- -- See Note [Repeated -optP hashing]
+setPgmP f = alterToolSettings (\s -> s { toolSettings_pgm_P = (pgm, map Option args)})
+ where (pgm:args) = words f
+addOptl f = alterToolSettings (\s -> s { toolSettings_opt_l = f : toolSettings_opt_l s})
+addOptc f = alterToolSettings (\s -> s { toolSettings_opt_c = f : toolSettings_opt_c s})
+addOptcxx f = alterToolSettings (\s -> s { toolSettings_opt_cxx = f : toolSettings_opt_cxx s})
+addOptP f = alterToolSettings $ \s -> s
+ { toolSettings_opt_P = f : toolSettings_opt_P s
+ , toolSettings_opt_P_fingerprint = fingerprintStrings (f : toolSettings_opt_P s)
+ }
+ -- See Note [Repeated -optP hashing]
where
fingerprintStrings ss = fingerprintFingerprints $ map fingerprintString ss
@@ -2710,27 +2705,6 @@ addGhciScript f d = d { ghciScripts = f : ghciScripts d}
setInteractivePrint f d = d { interactivePrint = Just f}
--- -----------------------------------------------------------------------------
--- Command-line options
-
--- | When invoking external tools as part of the compilation pipeline, we
--- pass these a sequence of options on the command-line. Rather than
--- just using a list of Strings, we use a type that allows us to distinguish
--- between filepaths and 'other stuff'. The reason for this is that
--- this type gives us a handle on transforming filenames, and filenames only,
--- to whatever format they're expected to be on a particular platform.
-data Option
- = FileOption -- an entry that _contains_ filename(s) / filepaths.
- String -- a non-filepath prefix that shouldn't be
- -- transformed (e.g., "/out=")
- String -- the filepath/filename portion
- | Option String
- deriving ( Eq )
-
-showOpt :: Option -> String
-showOpt (FileOption pre f) = pre ++ f
-showOpt (Option s) = s
-
-----------------------------------------------------------------------------
-- Setting the optimisation level
@@ -3031,64 +3005,66 @@ dynamic_flags_deps = [
------- Specific phases --------------------------------------------
-- need to appear before -pgmL to be parsed as LLVM flags.
, make_ord_flag defFlag "pgmlo"
- (hasArg (\f -> alterSettings (\s -> s { sPgm_lo = (f,[])})))
+ $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_lo = (f,[]) }
, make_ord_flag defFlag "pgmlc"
- (hasArg (\f -> alterSettings (\s -> s { sPgm_lc = (f,[])})))
+ $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_lc = (f,[]) }
, make_ord_flag defFlag "pgmi"
- (hasArg (\f -> alterSettings (\s -> s { sPgm_i = f})))
+ $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_i = f }
, make_ord_flag defFlag "pgmL"
- (hasArg (\f -> alterSettings (\s -> s { sPgm_L = f})))
+ $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_L = f }
, make_ord_flag defFlag "pgmP"
(hasArg setPgmP)
, make_ord_flag defFlag "pgmF"
- (hasArg (\f -> alterSettings (\s -> s { sPgm_F = f})))
+ $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_F = f }
, make_ord_flag defFlag "pgmc"
- (hasArg (\f -> alterSettings (\s -> s { sPgm_c = (f,[]),
- -- Don't pass -no-pie with -pgmc
- -- (see #15319)
- sGccSupportsNoPie = False})))
+ $ hasArg $ \f -> alterToolSettings $ \s -> s
+ { toolSettings_pgm_c = (f,[])
+ , -- Don't pass -no-pie with -pgmc
+ -- (see #15319)
+ toolSettings_ccSupportsNoPie = False
+ }
, make_ord_flag defFlag "pgms"
(HasArg (\_ -> addWarn "Object splitting was removed in GHC 8.8"))
, make_ord_flag defFlag "pgma"
- (hasArg (\f -> alterSettings (\s -> s { sPgm_a = (f,[])})))
+ $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_a = (f,[]) }
, make_ord_flag defFlag "pgml"
- (hasArg (\f -> alterSettings (\s -> s { sPgm_l = (f,[])})))
+ $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_l = (f,[]) }
, make_ord_flag defFlag "pgmdll"
- (hasArg (\f -> alterSettings (\s -> s { sPgm_dll = (f,[])})))
+ $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_dll = (f,[]) }
, make_ord_flag defFlag "pgmwindres"
- (hasArg (\f -> alterSettings (\s -> s { sPgm_windres = f})))
+ $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_windres = f }
, make_ord_flag defFlag "pgmlibtool"
- (hasArg (\f -> alterSettings (\s -> s { sPgm_libtool = f})))
+ $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_libtool = f }
, make_ord_flag defFlag "pgmar"
- (hasArg (\f -> alterSettings (\s -> s { sPgm_ar = f})))
+ $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_ar = f }
, make_ord_flag defFlag "pgmranlib"
- (hasArg (\f -> alterSettings (\s -> s { sPgm_ranlib = f})))
+ $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_ranlib = f }
-- need to appear before -optl/-opta to be parsed as LLVM flags.
, make_ord_flag defFlag "optlo"
- (hasArg (\f -> alterSettings (\s -> s { sOpt_lo = f : sOpt_lo s})))
+ $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_opt_lo = f : toolSettings_opt_lo s }
, make_ord_flag defFlag "optlc"
- (hasArg (\f -> alterSettings (\s -> s { sOpt_lc = f : sOpt_lc s})))
+ $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_opt_lc = f : toolSettings_opt_lc s }
, make_ord_flag defFlag "opti"
- (hasArg (\f -> alterSettings (\s -> s { sOpt_i = f : sOpt_i s})))
+ $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_opt_i = f : toolSettings_opt_i s }
, make_ord_flag defFlag "optL"
- (hasArg (\f -> alterSettings (\s -> s { sOpt_L = f : sOpt_L s})))
+ $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_opt_L = f : toolSettings_opt_L s }
, make_ord_flag defFlag "optP"
(hasArg addOptP)
, make_ord_flag defFlag "optF"
- (hasArg (\f -> alterSettings (\s -> s { sOpt_F = f : sOpt_F s})))
+ $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_opt_F = f : toolSettings_opt_F s }
, make_ord_flag defFlag "optc"
(hasArg addOptc)
, make_ord_flag defFlag "optcxx"
(hasArg addOptcxx)
, make_ord_flag defFlag "opta"
- (hasArg (\f -> alterSettings (\s -> s { sOpt_a = f : sOpt_a s})))
+ $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_opt_a = f : toolSettings_opt_a s }
, make_ord_flag defFlag "optl"
(hasArg addOptl)
, make_ord_flag defFlag "optwindres"
- (hasArg (\f ->
- alterSettings (\s -> s { sOpt_windres = f : sOpt_windres s})))
+ $ hasArg $ \f ->
+ alterToolSettings $ \s -> s { toolSettings_opt_windres = f : toolSettings_opt_windres s }
, make_ord_flag defGhcFlag "split-objs"
(NoArg $ addWarn "ignoring -split-objs")
@@ -5110,6 +5086,12 @@ unSetExtensionFlag' f dflags = xopt_unset dflags f
alterSettings :: (Settings -> Settings) -> DynFlags -> DynFlags
alterSettings f dflags = dflags { settings = f (settings dflags) }
+alterFileSettings :: (FileSettings -> FileSettings) -> DynFlags -> DynFlags
+alterFileSettings = alterSettings . \f settings -> settings { sFileSettings = f (sFileSettings settings) }
+
+alterToolSettings :: (ToolSettings -> ToolSettings) -> DynFlags -> DynFlags
+alterToolSettings = alterSettings . \f settings -> settings { sToolSettings = f (sToolSettings settings) }
+
--------------------------
setDumpFlag' :: DumpFlag -> DynP ()
setDumpFlag' dump_flag
@@ -5545,7 +5527,7 @@ splitPathList s = filter notNull (splitUp s)
-- tmpDir, where we store temporary files.
setTmpDir :: FilePath -> DynFlags -> DynFlags
-setTmpDir dir = alterSettings (\s -> s { sTmpDir = normalise dir })
+setTmpDir dir = alterFileSettings $ \s -> s { fileSettings_tmpDir = normalise dir }
-- we used to fix /cygdrive/c/.. on Windows, but this doesn't
-- seem necessary now --SDM 7/2/2008
diff --git a/compiler/main/FileSettings.hs b/compiler/main/FileSettings.hs
new file mode 100644
index 0000000000..f531d206a9
--- /dev/null
+++ b/compiler/main/FileSettings.hs
@@ -0,0 +1,16 @@
+module FileSettings
+ ( FileSettings (..)
+ ) where
+
+import GhcPrelude
+
+-- | Paths to various files and directories used by GHC, including those that
+-- provide more settings.
+data FileSettings = FileSettings
+ { fileSettings_ghcUsagePath :: FilePath -- ditto
+ , fileSettings_ghciUsagePath :: FilePath -- ditto
+ , fileSettings_toolDir :: Maybe FilePath -- ditto
+ , fileSettings_topDir :: FilePath -- ditto
+ , fileSettings_tmpDir :: String -- no trailing '/'
+ , fileSettings_systemPackageConfig :: FilePath
+ }
diff --git a/compiler/main/GhcNameVersion.hs b/compiler/main/GhcNameVersion.hs
new file mode 100644
index 0000000000..96e04186a7
--- /dev/null
+++ b/compiler/main/GhcNameVersion.hs
@@ -0,0 +1,11 @@
+module GhcNameVersion
+ ( GhcNameVersion (..)
+ ) where
+
+import GhcPrelude
+
+-- | Settings for what GHC this is.
+data GhcNameVersion = GhcNameVersion
+ { ghcNameVersion_programName :: String
+ , ghcNameVersion_projectVersion :: String
+ }
diff --git a/compiler/main/Settings.hs b/compiler/main/Settings.hs
new file mode 100644
index 0000000000..5a5f5ca3c9
--- /dev/null
+++ b/compiler/main/Settings.hs
@@ -0,0 +1,203 @@
+module Settings
+ ( Settings (..)
+ , sProgramName
+ , sProjectVersion
+ , sGhcUsagePath
+ , sGhciUsagePath
+ , sToolDir
+ , sTopDir
+ , sTmpDir
+ , sSystemPackageConfig
+ , sLdSupportsCompactUnwind
+ , sLdSupportsBuildId
+ , sLdSupportsFilelist
+ , sLdIsGnuLd
+ , sGccSupportsNoPie
+ , sPgm_L
+ , sPgm_P
+ , sPgm_F
+ , sPgm_c
+ , sPgm_a
+ , sPgm_l
+ , sPgm_dll
+ , sPgm_T
+ , sPgm_windres
+ , sPgm_libtool
+ , sPgm_ar
+ , 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_windres
+ , sOpt_lo
+ , sOpt_lc
+ , sOpt_lcc
+ , sOpt_i
+ , sExtraGccViaCFlags
+ , sTargetPlatformString
+ , sIntegerLibrary
+ , sIntegerLibraryType
+ , sGhcWithInterpreter
+ , sGhcWithNativeCodeGen
+ , sGhcWithSMP
+ , sGhcRTSWays
+ , sTablesNextToCode
+ , sLeadingUnderscore
+ , sLibFFI
+ , sGhcThreaded
+ , sGhcDebugged
+ , sGhcRtsWithLibdw
+ ) where
+
+import GhcPrelude
+
+import CliOption
+import Fingerprint
+import FileSettings
+import GhcNameVersion
+import Platform
+import PlatformConstants
+import ToolSettings
+
+data Settings = Settings
+ { sGhcNameVersion :: {-# UNPACk #-} !GhcNameVersion
+ , sFileSettings :: {-# UNPACK #-} !FileSettings
+ , sTargetPlatform :: Platform -- Filled in by SysTools
+ , sToolSettings :: {-# UNPACK #-} !ToolSettings
+ , sPlatformMisc :: {-# UNPACK #-} !PlatformMisc
+ , sPlatformConstants :: PlatformConstants
+
+ -- You shouldn't need to look things up in rawSettings directly.
+ -- They should have their own fields instead.
+ , sRawSettings :: [(String, String)]
+ }
+
+-----------------------------------------------------------------------------
+-- Accessessors from 'Settings'
+
+sProgramName :: Settings -> String
+sProgramName = ghcNameVersion_programName . sGhcNameVersion
+sProjectVersion :: Settings -> String
+sProjectVersion = ghcNameVersion_projectVersion . sGhcNameVersion
+
+sGhcUsagePath :: Settings -> FilePath
+sGhcUsagePath = fileSettings_ghcUsagePath . sFileSettings
+sGhciUsagePath :: Settings -> FilePath
+sGhciUsagePath = fileSettings_ghciUsagePath . sFileSettings
+sToolDir :: Settings -> Maybe FilePath
+sToolDir = fileSettings_toolDir . sFileSettings
+sTopDir :: Settings -> FilePath
+sTopDir = fileSettings_topDir . sFileSettings
+sTmpDir :: Settings -> String
+sTmpDir = fileSettings_tmpDir . sFileSettings
+sSystemPackageConfig :: Settings -> FilePath
+sSystemPackageConfig = fileSettings_systemPackageConfig . sFileSettings
+
+sLdSupportsCompactUnwind :: Settings -> Bool
+sLdSupportsCompactUnwind = toolSettings_ldSupportsCompactUnwind . sToolSettings
+sLdSupportsBuildId :: Settings -> Bool
+sLdSupportsBuildId = toolSettings_ldSupportsBuildId . sToolSettings
+sLdSupportsFilelist :: Settings -> Bool
+sLdSupportsFilelist = toolSettings_ldSupportsFilelist . sToolSettings
+sLdIsGnuLd :: Settings -> Bool
+sLdIsGnuLd = toolSettings_ldIsGnuLd . sToolSettings
+sGccSupportsNoPie :: Settings -> Bool
+sGccSupportsNoPie = toolSettings_ccSupportsNoPie . sToolSettings
+
+sPgm_L :: Settings -> String
+sPgm_L = toolSettings_pgm_L . sToolSettings
+sPgm_P :: Settings -> (String, [Option])
+sPgm_P = toolSettings_pgm_P . sToolSettings
+sPgm_F :: Settings -> String
+sPgm_F = toolSettings_pgm_F . sToolSettings
+sPgm_c :: Settings -> (String, [Option])
+sPgm_c = toolSettings_pgm_c . sToolSettings
+sPgm_a :: Settings -> (String, [Option])
+sPgm_a = toolSettings_pgm_a . sToolSettings
+sPgm_l :: Settings -> (String, [Option])
+sPgm_l = toolSettings_pgm_l . sToolSettings
+sPgm_dll :: Settings -> (String, [Option])
+sPgm_dll = toolSettings_pgm_dll . sToolSettings
+sPgm_T :: Settings -> String
+sPgm_T = toolSettings_pgm_T . sToolSettings
+sPgm_windres :: Settings -> String
+sPgm_windres = toolSettings_pgm_windres . sToolSettings
+sPgm_libtool :: Settings -> String
+sPgm_libtool = toolSettings_pgm_libtool . sToolSettings
+sPgm_ar :: Settings -> String
+sPgm_ar = toolSettings_pgm_ar . sToolSettings
+sPgm_ranlib :: Settings -> String
+sPgm_ranlib = toolSettings_pgm_ranlib . sToolSettings
+sPgm_lo :: Settings -> (String, [Option])
+sPgm_lo = toolSettings_pgm_lo . sToolSettings
+sPgm_lc :: Settings -> (String, [Option])
+sPgm_lc = toolSettings_pgm_lc . sToolSettings
+sPgm_lcc :: Settings -> (String, [Option])
+sPgm_lcc = toolSettings_pgm_lcc . sToolSettings
+sPgm_i :: Settings -> String
+sPgm_i = toolSettings_pgm_i . sToolSettings
+sOpt_L :: Settings -> [String]
+sOpt_L = toolSettings_opt_L . sToolSettings
+sOpt_P :: Settings -> [String]
+sOpt_P = toolSettings_opt_P . sToolSettings
+sOpt_P_fingerprint :: Settings -> Fingerprint
+sOpt_P_fingerprint = toolSettings_opt_P_fingerprint . sToolSettings
+sOpt_F :: Settings -> [String]
+sOpt_F = toolSettings_opt_F . sToolSettings
+sOpt_c :: Settings -> [String]
+sOpt_c = toolSettings_opt_c . sToolSettings
+sOpt_cxx :: Settings -> [String]
+sOpt_cxx = toolSettings_opt_cxx . sToolSettings
+sOpt_a :: Settings -> [String]
+sOpt_a = toolSettings_opt_a . sToolSettings
+sOpt_l :: Settings -> [String]
+sOpt_l = toolSettings_opt_l . sToolSettings
+sOpt_windres :: Settings -> [String]
+sOpt_windres = toolSettings_opt_windres . sToolSettings
+sOpt_lo :: Settings -> [String]
+sOpt_lo = toolSettings_opt_lo . sToolSettings
+sOpt_lc :: Settings -> [String]
+sOpt_lc = toolSettings_opt_lc . sToolSettings
+sOpt_lcc :: Settings -> [String]
+sOpt_lcc = toolSettings_opt_lcc . sToolSettings
+sOpt_i :: Settings -> [String]
+sOpt_i = toolSettings_opt_i . sToolSettings
+
+sExtraGccViaCFlags :: Settings -> [String]
+sExtraGccViaCFlags = toolSettings_extraGccViaCFlags . sToolSettings
+
+sTargetPlatformString :: Settings -> String
+sTargetPlatformString = platformMisc_targetPlatformString . sPlatformMisc
+sIntegerLibrary :: Settings -> String
+sIntegerLibrary = platformMisc_integerLibrary . sPlatformMisc
+sIntegerLibraryType :: Settings -> IntegerLibrary
+sIntegerLibraryType = platformMisc_integerLibraryType . sPlatformMisc
+sGhcWithInterpreter :: Settings -> Bool
+sGhcWithInterpreter = platformMisc_ghcWithInterpreter . sPlatformMisc
+sGhcWithNativeCodeGen :: Settings -> Bool
+sGhcWithNativeCodeGen = platformMisc_ghcWithNativeCodeGen . sPlatformMisc
+sGhcWithSMP :: Settings -> Bool
+sGhcWithSMP = platformMisc_ghcWithSMP . sPlatformMisc
+sGhcRTSWays :: Settings -> String
+sGhcRTSWays = platformMisc_ghcRTSWays . sPlatformMisc
+sTablesNextToCode :: Settings -> Bool
+sTablesNextToCode = platformMisc_tablesNextToCode . sPlatformMisc
+sLeadingUnderscore :: Settings -> Bool
+sLeadingUnderscore = platformMisc_leadingUnderscore . sPlatformMisc
+sLibFFI :: Settings -> Bool
+sLibFFI = platformMisc_libFFI . sPlatformMisc
+sGhcThreaded :: Settings -> Bool
+sGhcThreaded = platformMisc_ghcThreaded . sPlatformMisc
+sGhcDebugged :: Settings -> Bool
+sGhcDebugged = platformMisc_ghcDebugged . sPlatformMisc
+sGhcRtsWithLibdw :: Settings -> Bool
+sGhcRtsWithLibdw = platformMisc_ghcRtsWithLibdw . sPlatformMisc
diff --git a/compiler/main/SysTools.hs b/compiler/main/SysTools.hs
index b3dc60654e..763477a1c9 100644
--- a/compiler/main/SysTools.hs
+++ b/compiler/main/SysTools.hs
@@ -49,6 +49,7 @@ import Platform
import Util
import DynFlags
import Fingerprint
+import ToolSettings
import System.FilePath
import System.IO
@@ -282,68 +283,82 @@ initSysTools top_dir
ghcDebugged <- getBooleanSetting "Use Debugging"
ghcRtsWithLibdw <- getBooleanSetting "RTS expects libdw"
- return $ Settings {
- sTargetPlatform = platform,
- sTmpDir = normalise tmpdir,
- sGhcUsagePath = ghc_usage_msg_path,
- sGhciUsagePath = ghci_usage_msg_path,
- sToolDir = mtool_dir,
- sTopDir = top_dir,
- sRawSettings = mySettings,
- sExtraGccViaCFlags = words myExtraGccViaCFlags,
- sSystemPackageConfig = pkgconfig_path,
- sLdSupportsCompactUnwind = ldSupportsCompactUnwind,
- sLdSupportsBuildId = ldSupportsBuildId,
- sLdSupportsFilelist = ldSupportsFilelist,
- sLdIsGnuLd = ldIsGnuLd,
- sGccSupportsNoPie = gccSupportsNoPie,
- sProgramName = "ghc",
- sProjectVersion = cProjectVersion,
- sPgm_L = unlit_path,
- sPgm_P = (cpp_prog, cpp_args),
- sPgm_F = "",
- sPgm_c = (gcc_prog, gcc_args),
- sPgm_a = (as_prog, as_args),
- sPgm_l = (ld_prog, ld_args),
- sPgm_dll = (mkdll_prog,mkdll_args),
- sPgm_T = touch_path,
- sPgm_windres = windres_path,
- sPgm_libtool = libtool_path,
- sPgm_ar = ar_path,
- sPgm_ranlib = ranlib_path,
- sPgm_lo = (lo_prog,[]),
- sPgm_lc = (lc_prog,[]),
- sPgm_lcc = (lcc_prog,[]),
- sPgm_i = iserv_prog,
- sOpt_L = [],
- sOpt_P = [],
- sOpt_P_fingerprint = fingerprint0,
- sOpt_F = [],
- sOpt_c = [],
- sOpt_cxx = [],
- sOpt_a = [],
- sOpt_l = [],
- sOpt_windres = [],
- sOpt_lcc = [],
- sOpt_lo = [],
- sOpt_lc = [],
- sOpt_i = [],
- sPlatformConstants = platformConstants,
-
- sTargetPlatformString = targetPlatformString,
- sIntegerLibrary = integerLibrary,
- sIntegerLibraryType = integerLibraryType,
- sGhcWithInterpreter = ghcWithInterpreter,
- sGhcWithNativeCodeGen = ghcWithNativeCodeGen,
- sGhcWithSMP = ghcWithSMP,
- sGhcRTSWays = ghcRTSWays,
- sTablesNextToCode = tablesNextToCode,
- sLeadingUnderscore = leadingUnderscore,
- sLibFFI = useLibFFI,
- sGhcThreaded = ghcThreaded,
- sGhcDebugged = ghcDebugged,
- sGhcRtsWithLibdw = ghcRtsWithLibdw
- }
+ return $ Settings
+ { sGhcNameVersion = GhcNameVersion
+ { ghcNameVersion_programName = "ghc"
+ , ghcNameVersion_projectVersion = cProjectVersion
+ }
+
+ , sFileSettings = FileSettings
+ { fileSettings_tmpDir = normalise tmpdir
+ , fileSettings_ghcUsagePath = ghc_usage_msg_path
+ , fileSettings_ghciUsagePath = ghci_usage_msg_path
+ , fileSettings_toolDir = mtool_dir
+ , fileSettings_topDir = top_dir
+ , fileSettings_systemPackageConfig = pkgconfig_path
+ }
+
+ , sToolSettings = ToolSettings
+ { toolSettings_ldSupportsCompactUnwind = ldSupportsCompactUnwind
+ , toolSettings_ldSupportsBuildId = ldSupportsBuildId
+ , toolSettings_ldSupportsFilelist = ldSupportsFilelist
+ , toolSettings_ldIsGnuLd = ldIsGnuLd
+ , toolSettings_ccSupportsNoPie = gccSupportsNoPie
+
+ , toolSettings_pgm_L = unlit_path
+ , toolSettings_pgm_P = (cpp_prog, cpp_args)
+ , toolSettings_pgm_F = ""
+ , toolSettings_pgm_c = (gcc_prog, gcc_args)
+ , toolSettings_pgm_a = (as_prog, as_args)
+ , toolSettings_pgm_l = (ld_prog, ld_args)
+ , toolSettings_pgm_dll = (mkdll_prog,mkdll_args)
+ , toolSettings_pgm_T = touch_path
+ , toolSettings_pgm_windres = windres_path
+ , toolSettings_pgm_libtool = libtool_path
+ , toolSettings_pgm_ar = ar_path
+ , toolSettings_pgm_ranlib = ranlib_path
+ , toolSettings_pgm_lo = (lo_prog,[])
+ , toolSettings_pgm_lc = (lc_prog,[])
+ , toolSettings_pgm_lcc = (lcc_prog,[])
+ , toolSettings_pgm_i = iserv_prog
+ , toolSettings_opt_L = []
+ , toolSettings_opt_P = []
+ , toolSettings_opt_P_fingerprint = fingerprint0
+ , toolSettings_opt_F = []
+ , toolSettings_opt_c = []
+ , toolSettings_opt_cxx = []
+ , toolSettings_opt_a = []
+ , toolSettings_opt_l = []
+ , toolSettings_opt_windres = []
+ , toolSettings_opt_lcc = []
+ , toolSettings_opt_lo = []
+ , toolSettings_opt_lc = []
+ , toolSettings_opt_i = []
+
+ , toolSettings_extraGccViaCFlags = words myExtraGccViaCFlags
+ }
+
+ , sTargetPlatform = platform
+ , sPlatformMisc = PlatformMisc
+ { platformMisc_targetPlatformString = targetPlatformString
+ , platformMisc_integerLibrary = integerLibrary
+ , platformMisc_integerLibraryType = integerLibraryType
+ , platformMisc_ghcWithInterpreter = ghcWithInterpreter
+ , platformMisc_ghcWithNativeCodeGen = ghcWithNativeCodeGen
+ , platformMisc_ghcWithSMP = ghcWithSMP
+ , platformMisc_ghcRTSWays = ghcRTSWays
+ , platformMisc_tablesNextToCode = tablesNextToCode
+ , platformMisc_leadingUnderscore = leadingUnderscore
+ , platformMisc_libFFI = useLibFFI
+ , platformMisc_ghcThreaded = ghcThreaded
+ , platformMisc_ghcDebugged = ghcDebugged
+ , platformMisc_ghcRtsWithLibdw = ghcRtsWithLibdw
+ }
+
+ , sPlatformConstants = platformConstants
+
+ , sRawSettings = mySettings
+ }
{- Note [Windows stack usage]
diff --git a/compiler/main/ToolSettings.hs b/compiler/main/ToolSettings.hs
new file mode 100644
index 0000000000..e15c6923e2
--- /dev/null
+++ b/compiler/main/ToolSettings.hs
@@ -0,0 +1,64 @@
+module ToolSettings
+ ( ToolSettings (..)
+ ) where
+
+import GhcPrelude
+
+import CliOption
+import Fingerprint
+
+-- | Settings for other executables GHC calls.
+--
+-- Probably should futher split down by phase, or split between
+-- platform-specific and platform-agnostic.
+data ToolSettings = ToolSettings
+ { toolSettings_ldSupportsCompactUnwind :: Bool
+ , toolSettings_ldSupportsBuildId :: Bool
+ , toolSettings_ldSupportsFilelist :: Bool
+ , toolSettings_ldIsGnuLd :: Bool
+ , toolSettings_ccSupportsNoPie :: Bool
+
+ -- commands for particular phases
+ , toolSettings_pgm_L :: String
+ , toolSettings_pgm_P :: (String, [Option])
+ , toolSettings_pgm_F :: String
+ , toolSettings_pgm_c :: (String, [Option])
+ , toolSettings_pgm_a :: (String, [Option])
+ , toolSettings_pgm_l :: (String, [Option])
+ , toolSettings_pgm_dll :: (String, [Option])
+ , toolSettings_pgm_T :: String
+ , toolSettings_pgm_windres :: String
+ , toolSettings_pgm_libtool :: String
+ , toolSettings_pgm_ar :: String
+ , toolSettings_pgm_ranlib :: String
+ , -- | LLVM: opt llvm optimiser
+ toolSettings_pgm_lo :: (String, [Option])
+ , -- | LLVM: llc static compiler
+ toolSettings_pgm_lc :: (String, [Option])
+ , -- | LLVM: c compiler
+ toolSettings_pgm_lcc :: (String, [Option])
+ , toolSettings_pgm_i :: String
+
+ -- options for particular phases
+ , toolSettings_opt_L :: [String]
+ , toolSettings_opt_P :: [String]
+ , -- | cached Fingerprint of sOpt_P
+ -- See Note [Repeated -optP hashing]
+ toolSettings_opt_P_fingerprint :: Fingerprint
+ , toolSettings_opt_F :: [String]
+ , toolSettings_opt_c :: [String]
+ , toolSettings_opt_cxx :: [String]
+ , toolSettings_opt_a :: [String]
+ , toolSettings_opt_l :: [String]
+ , toolSettings_opt_windres :: [String]
+ , -- | LLVM: llvm optimiser
+ toolSettings_opt_lo :: [String]
+ , -- | LLVM: llc static compiler
+ toolSettings_opt_lc :: [String]
+ , -- | LLVM: c compiler
+ toolSettings_opt_lcc :: [String]
+ , -- | iserv options
+ toolSettings_opt_i :: [String]
+
+ , toolSettings_extraGccViaCFlags :: [String]
+ }
diff --git a/compiler/utils/Platform.hs b/compiler/utils/Platform.hs
index 449a62a5b6..5f7d939f0d 100644
--- a/compiler/utils/Platform.hs
+++ b/compiler/utils/Platform.hs
@@ -16,6 +16,9 @@ module Platform (
osMachOTarget,
osSubsectionsViaSymbols,
platformUsesFrameworks,
+
+ PlatformMisc(..),
+ IntegerLibrary(..),
)
where
@@ -160,3 +163,28 @@ osSubsectionsViaSymbols :: OS -> Bool
osSubsectionsViaSymbols OSDarwin = True
osSubsectionsViaSymbols _ = False
+-- | Platform-specific settings formerly hard-coded in Config.hs.
+--
+-- These should probably be all be triaged whether they can be computed from
+-- other settings or belong in another another place (like 'Platform' above).
+data PlatformMisc = PlatformMisc
+ { -- TODO Recalculate string from richer info?
+ platformMisc_targetPlatformString :: String
+ , platformMisc_integerLibrary :: String
+ , platformMisc_integerLibraryType :: IntegerLibrary
+ , platformMisc_ghcWithInterpreter :: Bool
+ , platformMisc_ghcWithNativeCodeGen :: Bool
+ , platformMisc_ghcWithSMP :: Bool
+ , platformMisc_ghcRTSWays :: String
+ , platformMisc_tablesNextToCode :: Bool
+ , platformMisc_leadingUnderscore :: Bool
+ , platformMisc_libFFI :: Bool
+ , platformMisc_ghcThreaded :: Bool
+ , platformMisc_ghcDebugged :: Bool
+ , platformMisc_ghcRtsWithLibdw :: Bool
+ }
+
+data IntegerLibrary
+ = IntegerGMP
+ | IntegerSimple
+ deriving (Read, Show, Eq)